updated diff for trace-based primitive debugger

Zoltan Somogyi zs at cs.mu.OZ.AU
Mon Feb 2 18:47:57 AEDT 1998


Since my mail yesterday, I modified the prompt and the mechanism whereby
the runtime system gets its hand on the address of the library procedure
to use to print the values of variables, and updated the debugger's test
case.

Use stack layout tables to transmit information to the tracer, to allow
the tracer to print the names and values of variables at CALL and EXIT ports.
Extend stack layout tables to permit this.

For the time being the tables do not contain information about how to fill
in pseudo-typeinfos, so printing only works for monomorphic procedures.
Another limitation is that printing only works for procedures whose interfaces
do not access registers beyond r10.

compiler/llds.m:
	Allow space for variable names in the information we gather about live
	variables at given labels. 

compiler/llds_out.m:
	Print out variable names in the information we gather about live
	variables at given labels in comments.

compiler/continuation_info.m:
	Include variable names in the information we gather about live
	variables at given labels. 

	Record the determinism of each procedure, not its code model.

compiler/{call_gen,code_gen,code_info}.m:
	Include the names of variables in the data given to
	continuation_info.m.

compiler/options.m:
	Add a new developer-only option, --procid-stack-layout, whose effect
	is to extend stack_layout structures with static info identifying the
	procedure. This is used by execution tracing, and could (should) be
	used by stack tracing and profiling.

	Rename --alternate-liveness as --typeinfo-liveness. This is more
	expressive. Later we should add a new option --trace-liveness, which
	preserves every variable until the end of the clause for use by
	the trace debugger.

compiler/handle_options.m:
	Handle the option implications of --procid-stack-layout.

compiler/stack_layout.m:
	Include the encoded determinism instead of the code model in stack
	layout tables.

	Include variable names in the live data section of stack layout tables
	if they are available.

	Include procedure identification information in the stack layout tables
	if --procid-stack-layout is set.

compiler/trace.m:
	Use the new interface to MR_trace.

compiler/*.m:
	Trivial changes following from the renaming of --alternate-liveness.

runtime/mercury_accurate_gc.h:
	Add macros to decode encoded determinisms.

	Define structs for accessing the stack layout tables.

runtime/{mercury_string,mercury_types}.h:
	Move the typedefs of Char, UnsignedChar, String and ConstString
	from mercury_string.h to mercury_types.h to avoid problems with
	circular #includes.

runtime/mercury_trace.[ch]:
	Revise the interface to MR_trace so that it takes the layout table
	of the procedure as an argument. From the layout table, we can get
	to the module name, predicate name, arity, mode number, and
	determinism of the procedure, so we don't need to pass these any more,
	reducing parameter passing overhead. We can also get to information
	about where the input and output arguments are. We now use this
	information to allow the user to print out the value of the arguments
	at the CALL and EXIT ports.

	Change the prompt to a less intrusive "mtrace> ".

runtime/mercury_wrapper.[ch]:
	Add a new global variable, MR_library_trace_browser. We reserve space
	for this variable in mercury_wrapper.c. It will be initialized by the
	automatically generated xxx_init.c file to point to the procedure
	that the tracer will invoke to let the user browse the values of
	variables. This mechanism allows the runtime to maintain its current
	ignorance about the contents of the standard library.

util/mkinit.c:
	Generate additional code in the xxx_init.c files to fill in the value
	of MR_library_trace_browser.

tests/misc_tests/debugger_test.{inp,exp}:
	Add a few printing commands into the input for this test case, and
	update the expected output.

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/call_gen.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/call_gen.m,v
retrieving revision 1.118
diff -u -u -r1.118 call_gen.m
--- call_gen.m	1998/01/25 05:05:17	1.118
+++ call_gen.m	1998/01/30 09:39:09
@@ -81,7 +81,7 @@
 :- import_module arg_info, type_util, mode_util, unify_proc, instmap.
 :- import_module trace, globals, options.
 :- import_module bool, int, list, assoc_list, tree, set, map.
-:- import_module std_util, require.
+:- import_module varset, std_util, require.
 
 %---------------------------------------------------------------------------%
 
@@ -460,10 +460,10 @@
 	{ set__list_to_set(Variables0, Vars0) },
 	{ set__difference(Vars0, Args, Vars1) },
 	code_info__get_globals(Globals),
-	{ globals__lookup_bool_option(Globals, alternate_liveness, 
-		AlternateLiveness) },
+	{ globals__lookup_bool_option(Globals, typeinfo_liveness, 
+		TypeinfoLiveness) },
 	( 
-		{ AlternateLiveness = yes }
+		{ TypeinfoLiveness = yes }
 	->
 		code_info__get_proc_info(ProcInfo),
 		{ proc_info_get_typeinfo_vars_setwise(ProcInfo, Vars1, 
@@ -784,6 +784,8 @@
 call_gen__insert_arg_livelvals([], _, _, LiveVals, LiveVals) --> [].
 call_gen__insert_arg_livelvals([Var - L | As], GC_Method, AfterCallInstMap, 
 		LiveVals0, LiveVals) -->
+	code_info__get_varset(VarSet),
+	{ varset__lookup_name(VarSet, Var, Name) },
 	(
 		{ GC_Method = accurate }
 	->
@@ -792,9 +794,9 @@
 		code_info__variable_type(Var, Type),
 		{ type_util__vars(Type, TypeVars) },
 		code_info__find_type_infos(TypeVars, TypeParams),
-		{ LiveVal = live_lvalue(R, var(Type, Inst), TypeParams) }
+		{ LiveVal = live_lvalue(R, var(Type, Inst), Name, TypeParams) }
 	;
-		{ LiveVal = live_lvalue(R, unwanted, []) }
+		{ LiveVal = live_lvalue(R, unwanted, Name, []) }
 	),
 	{ code_util__arg_loc_to_register(L, R) },
 	call_gen__insert_arg_livelvals(As, GC_Method, AfterCallInstMap, 
Index: compiler/code_gen.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/code_gen.m,v
retrieving revision 1.45
diff -u -u -r1.45 code_gen.m
--- code_gen.m	1998/01/25 05:05:22	1.45
+++ code_gen.m	1998/01/30 09:26:20
@@ -182,6 +182,7 @@
 generate_proc_code(ProcInfo, ProcId, PredId, ModuleInfo, Globals,
 		ContInfo0, CellCount0, ContInfo, CellCount, Proc) :-
 		% find out if the proc is deterministic/etc
+	proc_info_interface_determinism(ProcInfo, Detism),
 	proc_info_interface_code_model(ProcInfo, CodeModel),
 		% get the goal for this procedure
 	proc_info_goal(ProcInfo, Goal),
@@ -240,7 +241,7 @@
 		code_util__make_proc_label(ModuleInfo, PredId, ProcId,
 			ProcLabel),
 		continuation_info__add_proc_layout_info(proc(PredId, ProcId),
-			ProcLabel, TotalSlots, CodeModel, MaybeSuccipSlot,
+			ProcLabel, TotalSlots, Detism, MaybeSuccipSlot,
 			ContInfo1, ContInfo)
 	;
 		ContInfo = ContInfo1
@@ -420,12 +421,12 @@
 		{ code_gen__select_args_with_mode(Args, top_in, InVars,
 			InLvals) },
 
-		code_gen__generate_lvaltypes(InVars, InLvals, LvalTypes,
+		code_gen__generate_var_infos(InVars, InLvals, VarInfos,
 			TypeInfos),
 		
 		code_info__get_continuation_info(ContInfo0),
 		{ continuation_info__add_proc_entry_info(proc(PredId, ProcId),
-			LvalTypes, TypeInfos, ContInfo0, ContInfo) },
+			VarInfos, TypeInfos, ContInfo0, ContInfo) },
 		code_info__set_continuation_info(ContInfo)
 	;
 		[]
@@ -613,14 +614,14 @@
 			{ globals__lookup_bool_option(Globals,
 				trace_stack_layout, yes) }
 		->
-			code_gen__generate_lvaltypes(OutVars, OutLvals,
-				LvalTypes, TypeInfos),
+			code_gen__generate_var_infos(OutVars, OutLvals,
+				VarInfos, TypeInfos),
 			code_info__get_continuation_info(ContInfo0),
 			code_info__get_pred_id(PredId),
 			code_info__get_proc_id(ProcId),
-			{ continuation_info__add_proc_exit_info(proc(PredId,
-				ProcId), LvalTypes, TypeInfos, ContInfo0,
-				ContInfo) },
+			{ continuation_info__add_proc_exit_info(
+				proc(PredId, ProcId), VarInfos, TypeInfos,
+				ContInfo0, ContInfo) },
 			code_info__set_continuation_info(ContInfo),
 
 				% Make sure typeinfos are in livevals(...)
@@ -698,29 +699,31 @@
 	% typeinfo variable - lval pairs for any type variables in
 	% the types of the given variables.
 
-:- pred code_gen__generate_lvaltypes(list(var), list(lval),
-		assoc_list(lval, live_value_type), assoc_list(var, lval),
-		code_info, code_info).
-:- mode code_gen__generate_lvaltypes(in, in, out, out, in, out) is det.
-code_gen__generate_lvaltypes(Vars, Lvals, LvalTypes, TypeInfos) -->
+:- pred code_gen__generate_var_infos(list(var), list(lval),
+		list(var_info), assoc_list(var, lval), code_info, code_info).
+:- mode code_gen__generate_var_infos(in, in, out, out, in, out) is det.
+
+code_gen__generate_var_infos(Vars, Lvals, VarInfos, TypeInfos) -->
+	{ assoc_list__from_corresponding_lists(Vars, Lvals, VarLvals) },
+	code_info__get_proc_info(ProcInfo),
+	{ proc_info_vartypes(ProcInfo, VarTypes) },
 	code_info__get_instmap(InstMap),
-	list__map_foldl(code_info__variable_type, Vars, Types),
-	{ list__map(instmap__lookup_var(InstMap), Vars, Insts) },
-	{ assoc_list__from_corresponding_lists(Types, Insts,
-		TypeInsts) },
-	{ list__map(lambda([TypeInst::in, LiveType::out] is det, (
-			TypeInst = Type - Inst,
-			LiveType = var(Type, Inst))), 
-		TypeInsts, LiveTypes) },
+	code_info__get_varset(VarSet),
+	{ MakeVarInfo = lambda([VarLval::in, VarInfo::out] is det, (
+		VarLval = Var - Lval,
+		map__lookup(VarTypes, Var, Type),
+		instmap__lookup_var(InstMap, Var, Inst),
+		LiveType = var(Type, Inst),
+		varset__lookup_name(VarSet, Var, "V_", Name),
+		VarInfo = var_info(Lval, LiveType, Name)
+	)) }, 
+	{ list__map(MakeVarInfo, VarLvals, VarInfos) },
 
 	% XXX This doesn't work yet.
 	% { list__map(type_util__vars, Types, TypeVarsList) },
 	% { list__condense(TypeVarsList, TypeVars) },
 	% code_info__find_type_infos(TypeVars, TypeInfos),
-	{ TypeInfos = [] },
-
-	{ assoc_list__from_corresponding_lists(Lvals, LiveTypes,
-		LvalTypes) }.
+	{ TypeInfos = [] }.
 
 %---------------------------------------------------------------------------%
 
@@ -1206,7 +1209,7 @@
 		Instrn0 = call(Target, ReturnLabel, LiveVals0, CM)
 	->
 		Instrn  = call(Target, ReturnLabel, 
-			[live_lvalue(stackvar(StackLoc), succip, []) |
+			[live_lvalue(stackvar(StackLoc), succip, "", []) |
 			LiveVals0], CM)
 	;
 		Instrn = Instrn0
Index: compiler/code_info.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/code_info.m,v
retrieving revision 1.216
diff -u -u -r1.216 code_info.m
--- code_info.m	1998/01/13 10:11:14	1.216
+++ code_info.m	1998/01/30 09:37:32
@@ -2891,7 +2891,7 @@
 
 code_info__generate_temp_livelvals([], LiveInfo, LiveInfo).
 code_info__generate_temp_livelvals([Slot - StoredLval | Slots], LiveInfo0, 
-		[live_lvalue(Slot, LiveValueType, []) | LiveInfo1]) :-
+		[live_lvalue(Slot, LiveValueType, "", []) | LiveInfo1]) :-
 	code_info__get_live_value_type(StoredLval, LiveValueType),
 	code_info__generate_temp_livelvals(Slots, LiveInfo0, LiveInfo1).
 
@@ -2916,11 +2916,11 @@
 		code_info__get_live_value_type(lval(maxfr), MaxfrValueType),
 		code_info__get_live_value_type(lval(redoip(lval(maxfr))),
 			RedoipValueType),
-		LiveInfo2 = [live_lvalue(CurfrVar, CurfrValueType, []) | 
+		LiveInfo2 = [live_lvalue(CurfrVar, CurfrValueType, "", []) | 
 				LiveInfo1],
-		LiveInfo3 = [live_lvalue(MaxfrVar, MaxfrValueType, []) |
+		LiveInfo3 = [live_lvalue(MaxfrVar, MaxfrValueType, "", []) |
 				LiveInfo2],
-		LiveInfo  = [live_lvalue(RedoipVar, RedoipValueType, []) |
+		LiveInfo  = [live_lvalue(RedoipVar, RedoipValueType, "", []) |
 				LiveInfo3]
 	).
 
@@ -2931,6 +2931,8 @@
 code_info__livevals_to_livelvals([], _GC_Method, _, []) --> [].
 code_info__livevals_to_livelvals([Lval - Var | Ls], GC_Method, AfterCallInstMap,
 		[LiveLval | Lives]) -->
+	code_info__get_varset(VarSet),
+	{ varset__lookup_name(VarSet, Var, Name) },
 	(
 		{ GC_Method = accurate }
 	->
@@ -2939,9 +2941,10 @@
 		code_info__variable_type(Var, Type),
 		{ type_util__vars(Type, TypeVars) },
 		code_info__find_type_infos(TypeVars, TypeParams),
-		{ LiveLval = live_lvalue(Lval, var(Type, Inst), TypeParams) }
+		{ LiveLval = live_lvalue(Lval, var(Type, Inst), Name,
+			TypeParams) }
 	;
-		{ LiveLval = live_lvalue(Lval, unwanted, []) }
+		{ LiveLval = live_lvalue(Lval, unwanted, Name, []) }
 	),
 	code_info__livevals_to_livelvals(Ls, GC_Method, AfterCallInstMap, 
 		Lives).
Index: compiler/continuation_info.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/continuation_info.m,v
retrieving revision 1.8
diff -u -u -r1.8 continuation_info.m
--- continuation_info.m	1998/01/25 05:05:25	1.8
+++ continuation_info.m	1998/01/30 09:28:23
@@ -3,12 +3,13 @@
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
 %-----------------------------------------------------------------------------%
-
+%
 % File: continuation_info.m.
 % Main author: trd.
-
+%
 % This file defines the continuation_info data structure, which is used
-% to hold the information we need to output stack_layout tables for
+% to hold the information we need to output stack_layout tables, 
+% are for
 % accurate garbage collection.
 %
 % Information is collected in several passes. 
@@ -19,10 +20,12 @@
 %		- during the generation of the procedure's epilog code 
 %		  (in code_gen.m) we add the information about live
 %		  values at exit.
+%
 % 	- If basic_stack_layouts are needed, after code for a procedure
 % 	  has been generated, the proc_layout_general_info is added to
 % 	  the continuation_info, and some internal label information
 % 	  is initialized (but not filled in with live values).
+%
 % 	- If agc_stack_layouts are needed, after the code has been
 % 	  optimized a pass is made over the final LLDS instructions.
 % 	  Information about internal labels, is collected.  The liveness
@@ -41,7 +44,7 @@
 
 :- interface.
 
-:- import_module llds, hlds_pred.
+:- import_module llds, hlds_pred, hlds_data.
 :- import_module list.
 
 	%
@@ -66,8 +69,7 @@
 	% with entries (if required).
 	%
 :- type proc_layout_info
-	--->
-		proc_layout_info(
+	--->	proc_layout_info(
 			maybe(proc_layout_general_info),
 					% information on the procedure,
 					% needed for basic_stack_layouts
@@ -77,17 +79,15 @@
 			maybe(continuation_label_info),  % entry
 			maybe(continuation_label_info)	 % exit
 					% live data information about
-					% entry and exit points
-					% needed for
-					% trace_stack_layouts
+					% entry and exit points,
+					% needed for trace_stack_layouts
 		).
 
 :- type proc_layout_general_info
-	--->
-		proc_layout_general_info(
+	--->	proc_layout_general_info(
 			proc_label,	% the proc label
+			determinism,	% which stack is used
 			int,		% number of stack slots
-			code_model,	% which stack is used
 			maybe(int)	% location of succip on stack
 		).
 
@@ -96,8 +96,7 @@
 	% (Continuation labels are a special case of internal labels).
 	%
 :- type internal_layout_info
-	--->
-		internal_layout_info(
+	--->	internal_layout_info(
 			maybe(continuation_label_info)
 				% needed for agc_stack_layouts
 		).
@@ -113,15 +112,19 @@
 	% is easy if we represent the live values and type infos as
 	% sets.
 :- type continuation_label_info
-	--->
-		continuation_label_info(
-			set(pair(lval, live_value_type)),
-					% live values and their
-					% locations
+	--->	continuation_label_info(
+			set(var_info),
+				% live vars and their locations/names
 			set(pair(tvar, lval))
 				% locations of polymorphic type vars
 		).
 
+:- type var_info
+	--->	var_info(
+			lval,		% the location of the variable
+			live_value_type,% pseudo-typeinfo giving the var's type
+			string		% the var's name
+		).
 
 	% Return an initialized continuation info structure.
 
@@ -136,18 +139,18 @@
 	% in this proc (if there is one).
 	%
 :- pred continuation_info__add_proc_layout_info(pred_proc_id, proc_label,
-		int, code_model, maybe(int), continuation_info,
+		int, determinism, maybe(int), continuation_info,
 		continuation_info).
 :- mode continuation_info__add_proc_layout_info(in, in, in, in, in, in,
 		out) is det.
 
 :- pred continuation_info__add_proc_entry_info(pred_proc_id, 
-		assoc_list(lval, live_value_type), assoc_list(var, lval),
+		list(var_info), assoc_list(var, lval),
 		continuation_info, continuation_info).
 :- mode continuation_info__add_proc_entry_info(in, in, in, in, out) is det.
 
 :- pred continuation_info__add_proc_exit_info(pred_proc_id, 
-		assoc_list(lval, live_value_type), assoc_list(var, lval),
+		list(var_info), assoc_list(var, lval),
 		continuation_info, continuation_info).
 :- mode continuation_info__add_proc_exit_info(in, in, in, in, out) is det.
 
@@ -155,7 +158,6 @@
 		continuation_info, continuation_info) is det.
 :- mode continuation_info__process_llds(in, in, out) is det.
 
-
 	%
 	% Add the information for all the labels within a
 	% proc.
@@ -168,7 +170,6 @@
 	list(instruction), continuation_info, continuation_info).
 :- mode continuation_info__process_instructions(in, in, in, out) is det.
 
-
 	%
 	% Get the finished list of proc_layout_infos.
 	%
@@ -196,7 +197,6 @@
 				% in the current procedure
 			).
 
-
 %-----------------------------------------------------------------------------%
 
 	% Exported predicates.
@@ -271,20 +271,19 @@
 	continuation_info__get_internal_info(InternalInfo),
 	continuation_info__add_internal_info_to_proc(PredProcId, InternalInfo).
 
-
 	%
 	% Add the info for this proc (a proc_layout_info) to the
 	% continuation_info. 
 	%
 continuation_info__add_proc_layout_info(PredProcId, ProcLabel, StackSize,
-		CodeModel, SuccipLocation) -->
+		Detism, SuccipLocation) -->
 	continuation_info__get_proc_layout(PredProcId, ProcLayoutInfo0),
 	{ 
 		ProcLayoutInfo0 = proc_layout_info(no, InternalMap, 
 			EntryInfo, ExitInfo) 
 	->
 		ProcLayoutInfo = proc_layout_info(yes(proc_layout_general_info(
-			ProcLabel, StackSize, CodeModel, SuccipLocation)), 
+			ProcLabel, Detism, StackSize, SuccipLocation)), 
 			InternalMap, EntryInfo, ExitInfo)
 	;
 		error("continuation_info__add_proc_layout_info: general information already done.")
@@ -314,7 +313,6 @@
 		InternalInfo0, InternalInfo) },
 	continuation_info__set_internal_info(InternalInfo).
 
-
 	%
 	% Add a label to the internals, if it isn't already there.
 	%
@@ -341,23 +339,23 @@
 
 continuation_info__process_internal_info(Label - LiveInfoList, ContInfo0,
 		ContInfo) :-
+	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)
-		)),
-	GetLvalPair = lambda([LiveLval::in, LvalPair::out] is det, (
-		LiveLval = live_lvalue(Lval, LiveValueType, _),
-		LvalPair = Lval - LiveValueType
-		)),
-	list__map(GetLvalPair, LiveInfoList, LvalPairList),
+		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(LvalPairList, LvalPairSet),
+	set__list_to_set(VarInfoList, VarInfoSet),
 	NewInternal = internal_layout_info(
-		yes(continuation_label_info(LvalPairSet, TypeInfoSet))),
-	continuation_info__add_internal_info(Label, NewInternal, ContInfo0,
-		ContInfo).
+		yes(continuation_label_info(VarInfoSet, TypeInfoSet))),
+	continuation_info__add_internal_info(Label, NewInternal,
+		ContInfo0, ContInfo).
 
 	%
 	% Merge the continuation label information of two labels.
@@ -393,7 +391,6 @@
 
 	% Procedures to manipulate continuation_info
 
-
 	%
 	% Add the given proc_layout_info to the continuation_info.
 	%
@@ -522,7 +519,6 @@
 
 continuation_info__get_internal_info(InternalMap, ContInfo, ContInfo) :-
 	ContInfo = continuation_info(_, InternalMap).
-
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
Index: compiler/handle_options.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/handle_options.m,v
retrieving revision 1.41
diff -u -u -r1.41 handle_options.m
--- handle_options.m	1998/01/25 05:05:30	1.41
+++ handle_options.m	1998/01/29 05:41:36
@@ -260,7 +260,7 @@
 	% 	- disabling optimizations that would change 
 	% 	  the trace being generated
 	% 	- enabling stack layouts
-	% 	- enabling alternate liveness
+	% 	- enabling typeinfo liveness
 	globals__io_lookup_bool_option(generate_trace, Trace),
 	( { Trace = yes } ->
 		globals__io_set_option(inline_simple, bool(no)),
@@ -272,25 +272,28 @@
 		globals__io_set_option(optimize_constructor_last_call,
 			bool(no)),
 		globals__io_set_option(trace_stack_layout, bool(yes)),
-		globals__io_set_option(alternate_liveness, bool(yes))
+		globals__io_set_option(typeinfo_liveness, bool(yes))
 	;
 		[]
 	),
 
-	% --stack-trace requires basic stack layouts
-	option_implies(stack_trace, basic_stack_layout, bool(yes)),
+	% --stack-trace requires `procid' stack layouts
+	option_implies(stack_trace, procid_stack_layout, bool(yes)),
 
-	% --gc accurate requires stack layouts and alternate liveness.
+	% `trace' stack layouts need `procid' stack layouts
+	option_implies(trace_stack_layout, procid_stack_layout, bool(yes)),
+
+	% --gc accurate requires `agc' stack layouts and typeinfo liveness.
 	( { GC_Method = accurate } ->
 		globals__io_set_option(agc_stack_layout, bool(yes)),
-		globals__io_set_option(alternate_liveness, bool(yes)) 
+		globals__io_set_option(typeinfo_liveness, bool(yes)) 
 	;
 		[]
 	),
 
-	% `agc' and `trace' stack layouts need `basic' stack layouts
+	% `procid' and `agc' stack layouts need `basic' stack layouts
+	option_implies(procid_stack_layout, basic_stack_layout, bool(yes)),
 	option_implies(agc_stack_layout, basic_stack_layout, bool(yes)),
-	option_implies(trace_stack_layout, basic_stack_layout, bool(yes)),
 
 	% --dump-hlds and --statistics require compilation by phases
 	globals__io_lookup_accumulating_option(dump_hlds, DumpStages),
Index: compiler/live_vars.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/live_vars.m,v
retrieving revision 1.71
diff -u -u -r1.71 live_vars.m
--- live_vars.m	1998/01/25 05:05:35	1.71
+++ live_vars.m	1998/01/30 01:16:52
@@ -499,9 +499,10 @@
 maybe_add_alternate_liveness_typeinfos(ModuleInfo, ProcInfo, OutVars,
 		LiveVars1, LiveVars) :-
 	module_info_globals(ModuleInfo, Globals),
-	globals__lookup_bool_option(Globals, alternate_liveness, AlternateLive),
+	globals__lookup_bool_option(Globals, typeinfo_liveness,
+		TypeinfoLiveness),
 	(
-		AlternateLive = yes
+		TypeinfoLiveness = yes
 	->
 		proc_info_get_typeinfo_vars_setwise(ProcInfo, LiveVars1,
 			TypeInfoVarsLive),
Index: compiler/liveness.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/liveness.m,v
retrieving revision 1.89
diff -u -u -r1.89 liveness.m
--- liveness.m	1998/01/25 05:05:39	1.89
+++ liveness.m	1998/01/30 01:15:08
@@ -52,7 +52,7 @@
 % code at that resume point as well as the nature of the required
 % entry labels.
 %
-% Alternate liveness calculation notes:
+% Typeinfo liveness calculation notes:
 %
 % When using accurate gc or execution tracing, liveness is computed
 % slightly differently.  The runtime system needs access to the
@@ -884,10 +884,10 @@
 		% typeinfo vars.
 	proc_info_goal(ProcInfo, _Goal - GoalInfo),
 	goal_info_get_nonlocals(GoalInfo, NonLocals0),
-	globals__lookup_bool_option(Globals, alternate_liveness, 
-		AlternateLiveness),
+	globals__lookup_bool_option(Globals, typeinfo_liveness, 
+		TypeinfoLiveness),
 	( 	
-		AlternateLiveness = yes
+		TypeinfoLiveness = yes
 	->
 		proc_info_get_typeinfo_vars_setwise(ProcInfo, NonLocals0,
 			TypeInfoNonLocals),
@@ -936,10 +936,10 @@
 		% If doing alternate liveness, the corresponding
 		% typeinfos need to be added to these.
 	module_info_globals(ModuleInfo, Globals),
-	globals__lookup_bool_option(Globals, alternate_liveness, 
-		AlternateLiveness),
+	globals__lookup_bool_option(Globals, typeinfo_liveness, 
+		TypeinfoLiveness),
 	( 
-		AlternateLiveness = yes
+		TypeinfoLiveness = yes
 	->
 		proc_info_get_typeinfo_vars_setwise(ProcInfo, Deadness2,
 			TypeInfoVars),
@@ -1065,10 +1065,10 @@
 	live_info_get_module_info(LiveInfo, ModuleInfo),
 	module_info_globals(ModuleInfo, Globals),
 	goal_info_get_nonlocals(GoalInfo, NonLocals0),
-	globals__lookup_bool_option(Globals, alternate_liveness, 
-		AlternateLiveness),
+	globals__lookup_bool_option(Globals, typeinfo_liveness, 
+		TypeinfoLiveness),
 	( 
-		AlternateLiveness = yes
+		TypeinfoLiveness = yes
 	->
 		live_info_get_proc_info(LiveInfo, ProcInfo),
 		proc_info_get_typeinfo_vars_setwise(ProcInfo, NonLocals0,
Index: compiler/llds.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/llds.m,v
retrieving revision 1.220
diff -u -u -r1.220 llds.m
--- llds.m	1998/01/25 06:05:26	1.220
+++ llds.m	1998/01/30 09:29:08
@@ -334,6 +334,10 @@
 				% refer to?
 			live_value_type,
 				% What is the type of this live value?
+			string,
+				% What is the name of the variable stored here?
+				% The empty string if this lval does not
+				% store a variable.
 			assoc_list(tvar, lval)
 				% Where are the typeinfos that determine the
 				% types of the actual parameters of the type
Index: compiler/llds_out.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/llds_out.m,v
retrieving revision 1.71
diff -u -u -r1.71 llds_out.m
--- llds_out.m	1998/01/25 06:05:27	1.71
+++ llds_out.m	1998/01/30 09:33:10
@@ -1369,15 +1369,18 @@
 :- mode output_gc_livevals_2(in, di, uo) is det.
 
 output_gc_livevals_2([]) --> [].
-output_gc_livevals_2([live_lvalue(Lval, LiveValueType, TypeParams)|Lvals]) -->
+output_gc_livevals_2([LiveInfo | LiveInfos]) -->
+	{ LiveInfo = live_lvalue(Lval, LiveValueType, Name, TypeParams) },
 	io__write_string(" *\t"),
 	output_lval(Lval),
 	io__write_string("\t"),
+	io__write_string(Name),
+	io__write_string("\t"),
 	output_live_value_type(LiveValueType),
 	io__write_string("\t"),
 	output_gc_livevals_params(TypeParams),
 	io__write_string("\n"),
-	output_gc_livevals_2(Lvals).
+	output_gc_livevals_2(LiveInfos).
 
 :- pred output_gc_livevals_params(assoc_list(var, lval), io__state, io__state).
 :- mode output_gc_livevals_params(in, di, uo) is det.
Index: compiler/options.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/options.m,v
retrieving revision 1.222
diff -u -u -r1.222 options.m
--- options.m	1998/01/28 04:17:20	1.222
+++ options.m	1998/01/29 06:51:26
@@ -147,12 +147,15 @@
 				% accurate GC.
 		;	agc_stack_layout
 				% Stack layout information required to do
+				% procedure identification.
+		;	procid_stack_layout
+				% Stack layout information required to do
 				% tracing.
 		;	trace_stack_layout
-				% Use alternate calculation of liveness
+				% Use an alternate calculation of liveness
 				% where typeinfos are live for any live data
 				% the includes that type variable.
-		;	alternate_liveness
+		;	typeinfo_liveness
 		;	highlevel_c
 		;	unboxed_float
 	% Code generation options
@@ -410,8 +413,9 @@
 	type_layout		-	bool(yes),
 	basic_stack_layout	-	bool(no),
 	agc_stack_layout	-	bool(no),
+	procid_stack_layout	-	bool(no),
 	trace_stack_layout	-	bool(no),
-	alternate_liveness	-	bool(no),
+	typeinfo_liveness	-	bool(no),
 	highlevel_c		-	bool(no),
 	unboxed_float		-	bool(no)
 ]).
@@ -707,8 +711,9 @@
 long_option("type-layout",		type_layout).
 long_option("agc-stack-layout",		agc_stack_layout).
 long_option("basic-stack-layout",	basic_stack_layout).
+long_option("procid-stack-layout",	procid_stack_layout).
 long_option("trace-stack-layout",	trace_stack_layout).
-long_option("alternate-liveness",	alternate_liveness).
+long_option("typeinfo-liveness",	typeinfo_liveness).
 long_option("highlevel-C",		highlevel_c).
 long_option("highlevel-c",		highlevel_c).
 long_option("high-level-C",		highlevel_c).
@@ -1543,13 +1548,19 @@
 %	io__write_string("\t\taccurate garbage collection.\n"),
 %
 		% This is a developer only option.
+%	io__write_string("\t--procid-stack-layout\n"),
+%	io__write_string("\t(This option is not for general use.)\n"),
+%	io__write_string("\t\tGenerate the stack_layout structures required for\n"),
+%	io__write_string("\t\tlooking up procedure identification information.\n"),
+
+		% This is a developer only option.
 %	io__write_string("\t--trace-stack-layout\n"),
 %	io__write_string("\t(This option is not for general use.)\n"),
 %	io__write_string("\t\tGenerate the stack_layout structures required for\n"),
 %	io__write_string("\t\texecution tracing.\n"),
 
 		% This is a developer only option.
-%	io__write_string("\t--alternate-liveness\n"),
+%	io__write_string("\t--typeinfo-liveness\n"),
 %	io__write_string("\t(This option is not for general use.)\n"),
 %	io__write_string("\t\tUse an alternate technique for calculating liveness.\n"),
 %	io__write_string("\t\tKeeps typeinfo variables around for as long as any data\n"),
Index: compiler/stack_layout.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/stack_layout.m,v
retrieving revision 1.5
diff -u -u -r1.5 stack_layout.m
--- stack_layout.m	1998/01/25 05:06:13	1.5
+++ stack_layout.m	1998/02/01 06:26:45
@@ -8,67 +8,128 @@
 % hold the `stack_layout' structures of the stack frames defined by the
 % current module.
 %
-% The tables generated have a number of `create' rvals within them,
-% these are removed by llds_common.m to create static structures.
+% The tables generated have a number of `create' rvals within them.
+% llds_common.m converts these into static data structures.
 %
-% Author: trd.
+% We can create several types of stack layouts. Which kind we generate
+% depends on the values of several options.
+%
+% Main author: trd.
+% Modifications by zs.
 %
 %---------------------------------------------------------------------------%
 %
 % Data Stucture: stack_layouts
 %
-% For each procedure,
-% 	mercury_data__stack_layout__mercury__<proc_label>
-% containing:
+% If the option basic_stack_layout is set, we generate a stack layout table
+% for each procedure. This table will be stored in the global variable
+% whose name is
+%	mercury_data__stack_layout__mercury__<proc_label>.
+% This table will always contain the following information:
+%
 %	code address		(Code *) - address of entry
-% 	number of stack slots	(Integer) 
-% 	code_model		(Integer) actually, type MR_Code_Model 
-% 					0 = DET, 1 = NONDET
+% 	determinism		(Integer) actually, type MR_determinism
+% 	number of stack slots	(Integer)
 % 	succip stack location	(Integer) actually, type MR_Live_Lval
 % 					(the location will be set to -1
 % 					if there is no succip available).
 %
-% If we are doing execution tracing, it will also include information
-% on the live data at entry and exit:
-% 	number of live 		(Integer)
-% 	    variables at entry 
-% 	live data locations and (Word *) - pointer to vector of
-% 	    types			MR_Live_Lval and MR_Live_Type pairs
-%	type parameters		(Word *) - pointer to vector of 
-%					MR_Live_Lval
-%
-% 	number of live 		(Integer)
-% 	    variables at exit 
-% 	live data locations and (Word *) - pointer to vector of
-% 	    types			MR_Live_Lval and MR_Live_Type pairs
-%	type parameters		(Word *) - pointer to vector of 
-%					MR_Live_Lval
-%
-% For each continuation label in a procedure
-% 	mercury_data__stack_layout__mercury__<proc_label>_i<label number>
-% containing:
-%	procedure info		(Word *) - pointer to procedure stack layout
-%	number of live vars	(Integer)
-%	live data locations and (Word *) - pointer to vector of 
-%		types			MR_Live_Lval and MR_Live_Type pairs
-%	type parameters		(Word *) - pointer to vector of 
-%					MR_Live_Lval
-%
-% If the number of live vars is 0, there could be two explanations. The
-% continuation label might actually have no live data, or (more likely)
-% it isn't a continuation label at all.
-%
-% If you need to know the live variables at non-continuation labels,
-% this code will not be sufficient. In particular, it is expected that
-% information about live variables at entry and exit points will be
-% added.
+% if the option procid_stack_layout is set, i.e. if we are doing stack
+% tracing, execution tracing or profiling, the table will also include
+% information on the identity of the procedure. This information will take
+% one of two forms. Almost all procedures use the first form:
+%
+%	predicate/function	(Int) actually, MR_pred_func
+%	declaring module name	(String)
+%	defining module name	(String)
+%	predicate name		(String)
+%	predicate arity		(Integer)
+%	procedure number	(Integer)
+%
+% Automatically generated unification, index and comparison predicates
+% use the second form:
+%
+%	type name		(String)
+%	type module's name	(String)
+%	defining module name	(String)
+%	predicate name		(String)
+%	predicate arity		(Integer)
+%	procedure number	(Integer)
+%
+% The runtime system can figure out which form is present by testing
+% the value of the first slot. A value of 0 or 1 indicates the first form;
+% any higher value indicates the second form.
+%
+% The meanings of the fields in both forms are the same as in procedure labels.
+%
+% If the option trace_stack_layout is set, i.e. if we are doing execution
+% tracing, the table will also include information on the variables that are
+% live at entry to and exit from the procedure:
+%
+% 	# of live vars at entry	(Integer)
+% 	live data pairs 	(Word *) - pointer to vector of pairs
+%				containing MR_Live_Lval and MR_Live_Type
+% 	live data names	 	(Word *) - pointer to vector of String
+%	type parameters		(Word *) - pointer to vector of MR_Live_Lval
+%
+% 	# of live vars at exit	(Integer)
+% 	live data pairs 	(Word *) - pointer to vector of pairs
+%				containing MR_Live_Lval and MR_Live_Type
+% 	live data names	 	(Word *) - pointer to vector of String
+%	type parameters		(Word *) - pointer to vector of MR_Live_Lval
+%
+% The live data pair vector will have an entry for each live variable.
+% The entry will give the location of the variable and its type (it also
+% has room for its instantiation state, but this is not filled in yet).
+%
+% The live data name vector pointer may be NULL. If it is not, the vector
+% will have an entry for each live variable, with each entry being either
+% NULL or giving the name of the variable.
 %
-% Note: That number of type parameters is stored as it is not needed --
+% The number of type parameters is never stored as it is not needed --
 % the type parameter vector will simply be indexed by the type parameter
-% number stored within pseudo-typeinfos. 
+% number stored within pseudo-typeinfos inside the elements of the live
+% data pairs vectors.
+%
+% If the option basic_stack_layout is set, we generate stack layout tables
+% for all labels internal to the procedure. This table will be stored in the
+% global variable whose name is
+%	mercury_data__stack_layout__mercury__<proc_label>_i<label_number>.
+% 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
+% 	live data names	 	(Word *) - pointer to vector of String
+% 	live data names	 	(Word *) - pointer to vector of String
+%	type parameters		(Word *) - pointer to vector of MR_Live_Lval
+%
+% We need detailed information about the variables that are live at an internal
+% label in two kinds of circumstances:
+%
+% -	the option trace_stack_layout is set, and the label represents
+%	a traced event (with the current set of events, this means the
+%	the entrance to one branch of a branched control structure)
+%
+% -	the option agc_stack_layout is set, and the label represents
+% 	a point where execution can resume after a procedure call or
+%	after backtracking.
+%
+% If either of these conditions holds for a given label at which there are some
+% live variables, all the fields above will be present in the stack layout
+% table for that label. However, the pointer to the live data names vector
+% will be NULL unless the first condition holds for the label (i.e. the label
+% is used in execution tracing).
+%
+% If neither condition holds for a given label, or if the number of live
+% variables at that label is zero, then the "# of live vars" field will be zero
+% and the last four fields will not be present.
 %
 % XXX: Presently, type parameter vectors are not created, and
-% inst information is ignored.
+% inst information is ignored. We also do not yet enable procid stack
+% layouts for profiling, since profiling does not yet use stack layouts.
 %
 %---------------------------------------------------------------------------%
 
@@ -84,26 +145,26 @@
 :- implementation.
 
 :- import_module llds, globals, options, continuation_info, llds_out.
-:- import_module base_type_layout, prog_data.
+:- import_module hlds_data, hlds_pred, base_type_layout, prog_data.
 :- import_module assoc_list, bool, string, int, list, map, std_util, require.
 :- import_module set.
 
 :- type stack_layout_info 	--->	
 	stack_layout_info(
 		string,		% module name
-		int,		% next available cell number 
+		int,		% next available cell number
 		bool,		% generate agc layout info?
 		bool,		% generate tracing layout info?
+		bool,		% generate procedure id layout info?
 		list(c_module)	% generated data
 	).
 
-
 %---------------------------------------------------------------------------%
 
 	% Initialize the StackLayoutInfo, and begin processing.
 stack_layout__generate_llds(ModuleInfo0, ModuleInfo, CModules) :-
 	module_info_get_continuation_info(ModuleInfo0, ContinuationInfo),
-	continuation_info__get_all_proc_layouts(ProcLayoutList, 
+	continuation_info__get_all_proc_layouts(ProcLayoutList,
 		ContinuationInfo, _),
 
 	module_info_name(ModuleInfo0, ModuleName),
@@ -111,9 +172,11 @@
 	module_info_globals(ModuleInfo0, Globals),
 	globals__lookup_bool_option(Globals, agc_stack_layout, AgcLayout),
 	globals__lookup_bool_option(Globals, trace_stack_layout, TraceLayout),
+	globals__lookup_bool_option(Globals, procid_stack_layout,
+		ProcInfoLayout),
 
 	LayoutInfo0 = stack_layout_info(ModuleName, CellCount, AgcLayout,
-		TraceLayout, []),
+		TraceLayout, ProcInfoLayout, []),
 	list__foldl(stack_layout__construct_layouts, ProcLayoutList,
 		LayoutInfo0, LayoutInfo),
 
@@ -125,13 +188,12 @@
 
 	% Construct the layouts for a single procedure.
 	
-:- pred stack_layout__construct_layouts(proc_layout_info, 
-		stack_layout_info, stack_layout_info).
-:- mode stack_layout__construct_layouts(in, in, out) is det.
+:- pred stack_layout__construct_layouts(proc_layout_info::in,
+		stack_layout_info::in, stack_layout_info::out) is det.
 
 stack_layout__construct_layouts(ProcLayoutInfo) -->
 
-	{ ProcLayoutInfo = proc_layout_info(MaybeGeneralInfo, InternalMap, 
+	{ ProcLayoutInfo = proc_layout_info(MaybeGeneralInfo, InternalMap,
 		EntryInfo, ExitInfo) },
 
 	( { MaybeGeneralInfo = yes(GeneralInfo) } ->
@@ -145,19 +207,19 @@
 		{ error("stack_layout__construct_layouts: uninitialized proc layout") }
 	).
 
-
 %---------------------------------------------------------------------------%
 
 	% Construct the layout describing a single procedure.
 
-:- pred stack_layout__construct_proc_layout(proc_layout_general_info,
-		maybe(continuation_label_info), maybe(continuation_label_info),
-		stack_layout_info, stack_layout_info).
-:- mode stack_layout__construct_proc_layout(in, in, in, in, out) is det.
+:- pred stack_layout__construct_proc_layout(proc_layout_general_info::in,
+		maybe(continuation_label_info)::in,
+		maybe(continuation_label_info)::in,
+		stack_layout_info::in, stack_layout_info::out) is det.
+
 stack_layout__construct_proc_layout(GeneralInfo, MaybeEntryInfo,
 		MaybeExitInfo) -->
-	{ GeneralInfo = proc_layout_general_info(ProcLabel, StackSlots, 
-		CodeModel, SuccipLoc) },
+	{ GeneralInfo = proc_layout_general_info(ProcLabel, Detism,
+		StackSlots, SuccipLoc) },
 	{
 		SuccipLoc = yes(Location0)
 	->
@@ -169,50 +231,92 @@
 			% upon what it is using the stack layouts for.
 		Location = -1
 	},
-	{
-		CodeModel = model_det,
-		SuccipLval = stackvar(Location)
+	{ determinism_components(Detism, _, at_most_many) ->
+		SuccipLval = framevar(Location)
 	;
-		CodeModel = model_semi,
 		SuccipLval = stackvar(Location)
-	;
-		CodeModel = model_non,
-		SuccipLval = framevar(Location)
 	},
 	{ Label = local(ProcLabel) },
 	{ stack_layout__represent_lval(SuccipLval, SuccipRval) },
 	{ StackSlotsRval = const(int_const(StackSlots)) },
 	{ CodeAddrRval = const(code_addr_const(label(Label))) },
 
-	stack_layout__represent_code_model(CodeModel, CodeModelRval),
-	{ MaybeRvals0 = [yes(CodeAddrRval), yes(StackSlotsRval), 
-		yes(CodeModelRval), yes(SuccipRval)] },
+	{ stack_layout__represent_determinism(Detism, DetismRval) },
+	{ MaybeRvals0 = [yes(CodeAddrRval), yes(DetismRval),
+		yes(StackSlotsRval), yes(SuccipRval)] },
 	stack_layout__get_module_name(ModuleName),
 
-	stack_layout__get_trace_stack_layout(TraceLayout),
+	stack_layout__get_procid_stack_layout(ProcIdLayout),
 	(
-		{ TraceLayout = yes }
+		{ ProcIdLayout = yes }
 	->
-		stack_layout__construct_trace_rvals(MaybeEntryInfo,
-			MaybeExitInfo, TraceRvals)
+		{ stack_layout__construct_procid_rvals(ProcLabel, IdRvals) },
+		{ list__append(MaybeRvals0, IdRvals, MaybeRvals1) },
+
+		stack_layout__get_trace_stack_layout(TraceLayout),
+		(
+			{ TraceLayout = yes }
+		->
+			stack_layout__construct_trace_rvals(MaybeEntryInfo,
+				MaybeExitInfo, TraceRvals),
+			{ list__append(MaybeRvals1, TraceRvals, MaybeRvals) }
+		;
+			{ MaybeRvals = MaybeRvals1 }
+		)
 	;
-		{ TraceRvals = [] }
+		{ MaybeRvals = MaybeRvals0 }
 	),
 
-	{ list__append(MaybeRvals0, TraceRvals, MaybeRvals) },
-
-	{ CModule = c_data(ModuleName, stack_layout(Label), yes, 
+	{ CModule = c_data(ModuleName, stack_layout(Label), yes,
 		MaybeRvals, []) },
 	stack_layout__add_cmodule(CModule).
 
 %---------------------------------------------------------------------------%
 
+:- pred stack_layout__construct_procid_rvals(proc_label::in,
+	list(maybe(rval))::out) is det.
+
+stack_layout__construct_procid_rvals(ProcLabel, Rvals) :-
+	(
+		ProcLabel = proc(DefModule, PredFunc, DeclModule,
+			PredName, Arity, ProcId),
+		stack_layout__represent_pred_or_func(PredFunc, PredFuncCode),
+		proc_id_to_int(ProcId, Mode),
+		Rvals = [
+				yes(const(int_const(PredFuncCode))),
+				yes(const(string_const(DeclModule))),
+				yes(const(string_const(DefModule))),
+				yes(const(string_const(PredName))),
+				yes(const(int_const(Arity))),
+				yes(const(int_const(Mode)))
+			]
+	;
+		ProcLabel = special_proc(DefModule, PredName, TypeModule,
+			TypeName, Arity, ProcId),
+		proc_id_to_int(ProcId, Mode),
+		Rvals = [
+				yes(const(string_const(TypeName))),
+				yes(const(string_const(TypeModule))),
+				yes(const(string_const(DefModule))),
+				yes(const(string_const(PredName))),
+				yes(const(int_const(Arity))),
+				yes(const(int_const(Mode)))
+			]
+	).
+
+:- pred stack_layout__represent_pred_or_func(pred_or_func::in, int::out) is det.
+
+stack_layout__represent_pred_or_func(predicate, 0).
+stack_layout__represent_pred_or_func(function, 1).
+
+%---------------------------------------------------------------------------%
+
 	% Construct the layout describing a single continuation label.
 
-:- pred stack_layout__construct_internal_layout(proc_label,
-		pair(label, internal_layout_info), 
-		stack_layout_info, stack_layout_info).
-:- mode stack_layout__construct_internal_layout(in, in, in, out) is det.
+:- pred stack_layout__construct_internal_layout(proc_label::in,
+	pair(label, internal_layout_info)::in,
+	stack_layout_info::in, stack_layout_info::out) is det.
+
 stack_layout__construct_internal_layout(ProcLabel, Label - Internal) -->
 		% generate the required rvals
 	stack_layout__get_module_name(ModuleName),
@@ -221,22 +325,21 @@
 
 	stack_layout__construct_agc_rvals(Internal, AgcRvals),
 
-	{ LayoutRvals = [yes(EntryAddrRval) | AgcRvals] }, 
+	{ LayoutRvals = [yes(EntryAddrRval) | AgcRvals] },
 
-	{ CModule = c_data(ModuleName, stack_layout(Label), yes, 
+	{ CModule = c_data(ModuleName, stack_layout(Label), yes,
 		LayoutRvals, []) },
 	stack_layout__add_cmodule(CModule).
 
-	
 	% Construct the rvals required for tracing.
 
-:- pred stack_layout__construct_trace_rvals(maybe(continuation_label_info), 
-		maybe(continuation_label_info), list(maybe(rval)),
-		stack_layout_info, stack_layout_info).
-:- mode stack_layout__construct_trace_rvals(in, in, out, in, out) is det.
+:- pred stack_layout__construct_trace_rvals(maybe(continuation_label_info)::in,
+	maybe(continuation_label_info)::in, list(maybe(rval))::out,
+	stack_layout_info::in, stack_layout_info::out) is det.
+
 stack_layout__construct_trace_rvals(MaybeEntryInfo, MaybeExitInfo,
 		RvalList) -->
-	( 
+	(
 		{ MaybeEntryInfo = yes(EntryInfo) },
 		{ MaybeExitInfo = yes(ExitInfo) }
 	->
@@ -251,15 +354,15 @@
 		{ error("stack_layout__construct_agc_rvals: entry or exit information not available.") }
 	).
 
-
 	% Construct the rvals required for accurate GC.
 
-:- pred stack_layout__construct_agc_rvals(internal_layout_info, 
-		list(maybe(rval)), stack_layout_info, stack_layout_info).
-:- mode stack_layout__construct_agc_rvals(in, out, in, out) is det.
+:- pred stack_layout__construct_agc_rvals(internal_layout_info::in,
+	list(maybe(rval))::out,
+	stack_layout_info::in, stack_layout_info::out) is det.
+
 stack_layout__construct_agc_rvals(Internal, RvalList) -->
 	stack_layout__get_agc_stack_layout(AgcStackLayout),
-	( 
+	(
 		{ AgcStackLayout = yes }
 	->
 		{ Internal = internal_layout_info(ContinuationLabelInfo) },
@@ -272,7 +375,7 @@
 		;
 			% This label is not being used as a continuation,
 			% or we are not doing accurate GC, so we record
-			% no live values here. 
+			% 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
@@ -285,55 +388,78 @@
 		stack_layout__construct_livelval_rvals(LiveLvalSet, TVars,
 			RvalList)
 	;
-		{ RvalList = [yes(const(int_const(0))), 
+		{ RvalList = [yes(const(int_const(0))),
 			yes(const(int_const(0)))] }
 	).
 
+%---------------------------------------------------------------------------%
 
 	% XXX Should also create Tvars.
 
-:- pred stack_layout__construct_livelval_rvals(set(pair(lval, live_value_type)),
-		set(pair(tvar, lval)), list(maybe(rval)), 
+:- 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.
+
 stack_layout__construct_livelval_rvals(LiveLvalSet, _TVars, RvalList) -->
 	{ set__to_sorted_list(LiveLvalSet, LiveLvals) },
 	{ list__length(LiveLvals, Length) },
 	{ LengthRval = const(int_const(Length)) },
-	stack_layout__construct_liveval_pairs(LiveLvals, LiveValRval),
+	stack_layout__construct_liveval_pairs(LiveLvals, LiveValRval,
+		NamesRval),
 
 		% XXX We don't yet generate tvars, so we use 0 as
 		% a dummy value.
 	{ TVarRval = const(int_const(0)) },
-	{ RvalList = [yes(LengthRval), yes(LiveValRval), yes(TVarRval)] }.
-
-
+	{ RvalList = [yes(LengthRval), yes(LiveValRval),
+		yes(NamesRval), yes(TVarRval)] }.
 
 %---------------------------------------------------------------------------%
 
-	% Construct a vector of (lval, live_value_type) pairs.
+	% Construct a vector of (lval, live_value_type) pairs,
+	% and a corresponding vector of variable names.
 
-:- pred stack_layout__construct_liveval_pairs(assoc_list(lval, live_value_type),
-		rval, stack_layout_info, stack_layout_info).
-:- mode stack_layout__construct_liveval_pairs(in, out, in, out) is det.
+:- pred stack_layout__construct_liveval_pairs(list(var_info)::in,
+	rval::out, rval::out, stack_layout_info::in, stack_layout_info::out)
+	is det.
+
+stack_layout__construct_liveval_pairs(LiveLvals, LocnVector, NameVector) -->
+	list__map_foldl(stack_layout__construct_liveval_pair, LiveLvals,
+		LocnTypePairs),
+	{ list__condense(LocnTypePairs, LocnTypeVectorArgs) },
+	stack_layout__get_next_cell_number(CNum1),
+	{ LocnVector = create(0, LocnTypeVectorArgs, no, CNum1,
+		"stack_layout_locn_vector") },
 
-stack_layout__construct_liveval_pairs(LiveLvals, Rval) -->
-	list__map_foldl(stack_layout__construct_liveval_pair, LiveLvals, 
-		RvalsList),
-	{ list__condense(RvalsList, Rvals) },
-	stack_layout__get_next_cell_number(CNum),
-	{ Rval = create(0, Rvals, no, CNum, "stack_layout_pair") }.
+	{ list__map(stack_layout__construct_liveval_name, LiveLvals, Names) },
+	stack_layout__get_next_cell_number(CNum2),
+	{ NameVector = create(0, Names, no, CNum2,
+		"stack_layout_name_vector") }.
 
 	% Construct a pair of (lval, live_value_type) representations.
 
-:- pred stack_layout__construct_liveval_pair(pair(lval, live_value_type),
-		list(maybe(rval)), stack_layout_info, stack_layout_info).
-:- mode stack_layout__construct_liveval_pair(in, out, in, out) is det.
+:- pred stack_layout__construct_liveval_pair(var_info::in,
+	list(maybe(rval))::out, stack_layout_info::in, stack_layout_info::out)
+	is det.
 
-stack_layout__construct_liveval_pair(Lval - LiveValueType, Rvals) -->
+stack_layout__construct_liveval_pair(var_info(Lval, LiveValueType, _),
+		MaybeRvals) -->
 	{ stack_layout__represent_lval(Lval, Rval0) },
 	stack_layout__represent_live_value_type(LiveValueType, Rval1),
-	{ Rvals = [yes(Rval0), yes(Rval1)] }.
+	{ MaybeRvals = [yes(Rval0), yes(Rval1)] }.
+
+:- pred stack_layout__construct_liveval_name(var_info::in, maybe(rval)::out)
+	is det.
+
+stack_layout__construct_liveval_name(var_info(_, _, Name), MaybeRval) :-
+	( Name = "" ->
+		% We prefer a null pointer to a pointer to an empty string,
+		% since this way we don't need many copies of the empty string.
+		Rval = const(int_const(0))
+	;
+		Rval = const(string_const(Name))
+	),
+	MaybeRval = yes(Rval).
 
 %---------------------------------------------------------------------------%
 
@@ -350,7 +476,7 @@
 
 :- pred stack_layout__represent_live_value_type(live_value_type, rval,
 	stack_layout_info, stack_layout_info).
-:- mode stack_layout__represent_live_value_type(in, out, in, out) is det. 
+:- mode stack_layout__represent_live_value_type(in, out, in, out) is det.
 
 stack_layout__represent_live_value_type(succip, Rval) -->
 	{ Rval = const(int_const(0)) }.
@@ -366,8 +492,8 @@
 	{ Rval = const(int_const(5)) }.
 stack_layout__represent_live_value_type(var(Type, _Inst), Rval) -->
 	stack_layout__get_cell_number(CNum0),
-	{ base_type_layout__construct_pseudo_type_info(Type, Rval0, CNum0,
-		CNum) },
+	{ base_type_layout__construct_pseudo_type_info(Type, Rval0,
+		CNum0, CNum) },
 	stack_layout__set_cell_number(CNum),
 		% XXX hack - don't yet write out insts
 	{ Rval1 = const(int_const(-1)) },
@@ -439,86 +565,112 @@
 	stack_layout__tag_bits(Bits),
 	TaggedValue = (Value << Bits) + Tag.
 
-	% Construct a represntation of  the code model.
+:- pred stack_layout__tag_bits(int::out) is det.
 
-:- pred stack_layout__represent_code_model(code_model, rval, stack_layout_info, 
-		stack_layout_info).
-:- mode stack_layout__represent_code_model(in, out, in, out) is det.
-stack_layout__represent_code_model(CodeModel, Rval) -->
+stack_layout__tag_bits(8).
+
+%---------------------------------------------------------------------------%
+
+	% Construct a representation of the interface determinism of a
+	% procedure. The code we have chosen is not sequential; instead
+	% it encodes the various properties of each determinism.
+	%
+	% The 8 bit is set iff the context is first_solution.
+	% The 4 bit is set iff the min number of solutions is more than zero.
+	% The 2 bit is set iff the max number of solutions is more than zero.
+	% The 1 bit is set iff the max number of solutions is more than one.
+
+:- pred stack_layout__represent_determinism(determinism::in, rval::out) is det.
+
+stack_layout__represent_determinism(Detism, const(int_const(Code))) :-
 	(
-		{ CodeModel = model_det },
-		{ Rval = const(int_const(0)) }
+		Detism = det,
+		Code = 6		/* 0110 */
+	;
+		Detism = semidet,	/* 0010 */
+		Code = 2
+	;
+		Detism = nondet,
+		Code = 3		/* 0011 */
 	;
-		{ CodeModel = model_semi },
-		{ Rval = const(int_const(0)) }
+		Detism = multidet,
+		Code = 7		/* 0111 */
 	;
-		{ CodeModel = model_non },
-		{ Rval = const(int_const(1)) }
+		Detism = erroneous,
+		Code = 4		/* 0100 */
+	;
+		Detism = failure,
+		Code = 0		/* 0000 */
+	;
+		Detism = cc_nondet,
+		Code = 10 		/* 1010 */
+	;
+		Detism = cc_multidet,
+		Code = 14		/* 1110 */
 	).
 
-:- pred stack_layout__code_model(code_model::in, int::out) is det.
-stack_layout__code_model(model_det, 0).
-stack_layout__code_model(model_semi, 0).
-stack_layout__code_model(model_non, 1).
-
-:- pred stack_layout__tag_bits(int::out) is det.
-stack_layout__tag_bits(8).
-
 %---------------------------------------------------------------------------%
 
 	% Access to the stack_layout data structure.
 
-:- pred stack_layout__get_module_name(string, stack_layout_info, 
-		stack_layout_info).
-:- mode stack_layout__get_module_name(out, in, out) is det.
+:- pred stack_layout__get_module_name(string::out,
+	stack_layout_info::in, stack_layout_info::out) is det.
+
 stack_layout__get_module_name(ModuleName, LayoutInfo, LayoutInfo) :-
-	LayoutInfo = stack_layout_info(ModuleName, _, _, _, _).
+	LayoutInfo = stack_layout_info(ModuleName, _, _, _, _, _).
+
+:- pred stack_layout__get_next_cell_number(int::out,
+	stack_layout_info::in, stack_layout_info::out) is det.
 
-:- pred stack_layout__get_next_cell_number(int, stack_layout_info,
-	stack_layout_info).
-:- mode stack_layout__get_next_cell_number(out, in, out) is det.
 stack_layout__get_next_cell_number(CNum0, LayoutInfo0, LayoutInfo) :-
-	LayoutInfo0 = stack_layout_info(A, CNum0, C, D, E),
+	LayoutInfo0 = stack_layout_info(A, CNum0, C, D, E, F),
 	CNum is CNum0 + 1,
-	LayoutInfo = stack_layout_info(A, CNum, C, D, E).
+	LayoutInfo = stack_layout_info(A, CNum, C, D, E, F).
+
+:- pred stack_layout__get_cell_number(int::out,
+	stack_layout_info::in, stack_layout_info::out) is det.
 
-:- pred stack_layout__get_cell_number(int, stack_layout_info,
-		stack_layout_info).
-:- mode stack_layout__get_cell_number(out, in, out) is det.
 stack_layout__get_cell_number(CNum, LayoutInfo, LayoutInfo) :-
-	LayoutInfo = stack_layout_info(_, CNum, _, _, _).
+	LayoutInfo = stack_layout_info(_, CNum, _, _, _, _).
+
+:- pred stack_layout__get_cmodules(list(c_module)::out,
+	stack_layout_info::in, stack_layout_info::out) is det.
 
-:- pred stack_layout__get_cmodules(list(c_module), stack_layout_info, 
-		stack_layout_info).
-:- mode stack_layout__get_cmodules(out, in, out) is det.
 stack_layout__get_cmodules(CModules, LayoutInfo, LayoutInfo) :-
-	LayoutInfo = stack_layout_info(_, _, _, _, CModules).
+	LayoutInfo = stack_layout_info(_, _, _, _, _, CModules).
+
+:- pred stack_layout__get_agc_stack_layout(bool::out,
+	stack_layout_info::in, stack_layout_info::out) is det.
 
-:- pred stack_layout__get_agc_stack_layout(bool, stack_layout_info, 
-		stack_layout_info).
-:- mode stack_layout__get_agc_stack_layout(out, in, out) is det.
 stack_layout__get_agc_stack_layout(AgcStackLayout, LayoutInfo, LayoutInfo) :-
-	LayoutInfo = stack_layout_info(_, _, AgcStackLayout, _, _).
+	LayoutInfo = stack_layout_info(_, _, AgcStackLayout, _, _, _).
+
+:- pred stack_layout__get_trace_stack_layout(bool::out,
+	stack_layout_info::in, stack_layout_info::out) is det.
 
-:- pred stack_layout__get_trace_stack_layout(bool, stack_layout_info, 
-		stack_layout_info).
-:- mode stack_layout__get_trace_stack_layout(out, in, out) is det.
 stack_layout__get_trace_stack_layout(TraceStackLayout, LayoutInfo,
 		LayoutInfo) :-
-	LayoutInfo = stack_layout_info(_, _, _, TraceStackLayout, _).
+	LayoutInfo = stack_layout_info(_, _, _, TraceStackLayout, _, _).
+
+:- pred stack_layout__get_procid_stack_layout(bool::out,
+	stack_layout_info::in, stack_layout_info::out) is det.
+
+stack_layout__get_procid_stack_layout(ProcIdStackLayout, LayoutInfo,
+		LayoutInfo) :-
+	LayoutInfo = stack_layout_info(_, _, _, _, ProcIdStackLayout, _).
+
+:- pred stack_layout__add_cmodule(c_module::in,
+	stack_layout_info::in, stack_layout_info::out) is det.
 
-:- pred stack_layout__add_cmodule(c_module, stack_layout_info,
-		stack_layout_info).
-:- mode stack_layout__add_cmodule(in, in, out) is det.
 stack_layout__add_cmodule(CModule, LayoutInfo0, LayoutInfo) :-
-	LayoutInfo0 = stack_layout_info(A, B, C, D, CModules0),
+	LayoutInfo0 = stack_layout_info(A, B, C, D, E, CModules0),
 	CModules = [CModule | CModules0],
-	LayoutInfo = stack_layout_info(A, B, C, D, CModules).
+	LayoutInfo = stack_layout_info(A, B, C, D, E, CModules).
+
+:- pred stack_layout__set_cell_number(int::in,
+	stack_layout_info::in, stack_layout_info::out) is det.
 
-:- pred stack_layout__set_cell_number(int, stack_layout_info,
-		stack_layout_info).
-:- mode stack_layout__set_cell_number(in, in, out) is det.
 stack_layout__set_cell_number(CNum, LayoutInfo0, LayoutInfo) :-
-	LayoutInfo0 = stack_layout_info(A, _, C, D, E),
-	LayoutInfo = stack_layout_info(A, CNum, C, D, E).
+	LayoutInfo0 = stack_layout_info(A, _, C, D, E, F),
+	LayoutInfo = stack_layout_info(A, CNum, C, D, E, F).
 
Index: compiler/trace.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/trace.m,v
retrieving revision 1.6
diff -u -u -r1.6 trace.m
--- trace.m	1998/01/24 05:44:24	1.6
+++ trace.m	1998/01/30 06:16:30
@@ -52,8 +52,8 @@
 
 :- implementation.
 
-:- import_module hlds_module, hlds_pred, tree.
-:- import_module int, list, std_util, string, require.
+:- import_module hlds_module, hlds_pred, llds_out, code_util, tree.
+:- import_module bool, int, list, std_util, string, require.
 
 :- type trace_info
 	--->	trace_info(
@@ -93,21 +93,15 @@
 	code_info__get_pred_id(PredId),
 	code_info__get_proc_id(ProcId),
 	code_info__get_module_info(ModuleInfo),
-	code_info__get_proc_model(CodeModel),
 	{
+	code_util__make_proc_label(ModuleInfo, PredId, ProcId, ProcLabel),
+	llds_out__get_label(local(ProcLabel), yes, LabelStr),
 	TraceInfo = trace_info(CallNumLval, CallDepthLval),
 	trace__stackref_to_string(CallNumLval, CallNumStr),
 	trace__stackref_to_string(CallDepthLval, CallDepthStr),
-	predicate_module(ModuleInfo, PredId, ModuleName),
-	predicate_name(ModuleInfo, PredId, PredName),
-	predicate_arity(ModuleInfo, PredId, Arity),
-	string__int_to_string(Arity, ArityStr),
 	Quote = """",
 	Comma = ", ",
 	trace__port_to_string(Port, PortStr),
-	trace__code_model_to_string(CodeModel, CodeModelStr),
-	proc_id_to_int(ProcId, ModeNum),
-	string__int_to_string(ModeNum, ModeNumStr),
 	( trace__port_path(Port, Path) ->
 		trace__path_to_string(Path, PathStr)
 	;
@@ -115,14 +109,10 @@
 	),
 	string__append_list([
 		"MR_trace(",
+		"(const Word *) &mercury_data__stack_layout__", LabelStr, Comma,
 		PortStr, Comma,
-		CodeModelStr, Comma,
 		CallNumStr, Comma,
 		CallDepthStr, Comma,
-		Quote, ModuleName, Quote, Comma,
-		Quote, PredName, Quote, Comma,
-		ArityStr, Comma,
-		ModeNumStr, Comma,
 		Quote, PathStr, Quote, ");\n"],
 		TraceStmt),
 	TraceCode = node([c_code(TraceStmt) - ""])
Index: compiler/unused_args.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/unused_args.m,v
retrieving revision 1.44
diff -u -u -r1.44 unused_args.m
--- unused_args.m	1998/01/29 13:24:33	1.44
+++ unused_args.m	1998/01/30 08:48:42
@@ -254,9 +254,9 @@
 			ArgModes, VarDep1, VarDep2),
 		
 		module_info_globals(ModuleInfo, Globals),
-		globals__lookup_bool_option(Globals, alternate_liveness, 
-			AlternateLiveness),
-		( AlternateLiveness = yes ->
+		globals__lookup_bool_option(Globals, typeinfo_liveness, 
+			TypeinfoLiveness),
+		( TypeinfoLiveness = yes ->
 			proc_info_typeinfo_varmap(ProcInfo, TVarMap),
 			setup_typeinfo_deps(Vars, VarTypes, 
 				proc(PredId, ProcId), TVarMap, VarDep2,
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/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/trailed_update
cvs diff: Diffing extras/trailed_update/samples
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_accurate_gc.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_accurate_gc.h,v
retrieving revision 1.5
diff -u -u -r1.5 mercury_accurate_gc.h
--- mercury_accurate_gc.h	1998/01/27 22:11:45	1.5
+++ mercury_accurate_gc.h	1998/02/02 04:24:39
@@ -29,10 +29,41 @@
 #endif
 
 /*
-** Definitions for MR_Stack_Specifier
+** Definitions for MR_PredFunc
 */
 
-typedef enum { MR_STACK_DET, MR_STACK_NONDET } MR_Stack_Specifier;
+typedef	enum { MR_PREDICATE, MR_FUNCTION } MR_PredFunc;
+
+/*
+** Definitions for MR_Determinism
+**
+** The max_soln component of the determinism is encoded in the 1 and 2 bits.
+** The can_fail component of the determinism is encoded in the 4 bit.
+** The first_solution component of the determinism is encoded in the 8 bit.
+**
+** MR_DETISM_AT_MOST_MANY could also be defined as ((d) & 3) == 3),
+** but this would be less efficient, since the C compiler does not know
+** that we do not set the 1 bit unless we also set the 2 bit.
+*/
+
+typedef	Word MR_Determinism;
+
+#define	MR_DETISM_DET		6
+#define	MR_DETISM_SEMI		2
+#define	MR_DETISM_NON		3
+#define	MR_DETISM_MULTI		7
+#define	MR_DETISM_ERRONEOUS	4
+#define	MR_DETISM_FAILURE	0
+#define	MR_DETISM_CCNON		10
+#define	MR_DETISM_CCMULTI	14
+
+#define MR_DETISM_AT_MOST_ZERO(d)	((d) & 3) == 0)
+#define MR_DETISM_AT_MOST_ONE(d)	((d) & 3) == 2)
+#define MR_DETISM_AT_MOST_MANY(d)	((d) & 1) != 0)
+
+#define MR_DETISM_CAN_FAIL(d)		((d) & 4) != 0)
+
+#define MR_DETISM_FIRST_SOLN(d)		((d) & 8) != 0)
 
 /*
 ** Definitions for "MR_Live_Lval"
@@ -128,7 +159,6 @@
 #define MR_LIVE_TYPE_GET_VAR_INST(T)   			\
 		((Word) ((MR_Var_Shape_Info *) T)->inst)
 
-
 /*
 ** Macros to support hand-written C code.
 */
@@ -147,8 +177,8 @@
 	Integer f4;							\
  } mercury_data__stack_layout__##l = {					\
 	STATIC(l),							\
+	(Integer) -1, 	/* Unknown determinism */			\
 	(Integer) -1,	/* Unknown number of stack slots */		\
-	(Integer) -1, 	/* Unknown code model */			\
         (Integer) MR_LVAL_TYPE_UNKNOWN 	/* Unknown succip location */	\
  };
 #else
@@ -207,13 +237,46 @@
  #define MR_MAKE_STACK_LAYOUT_INTERNAL(l, x)        
 #endif	/* MR_USE_STACK_LAYOUTS */
 
-
 /*
-** Macros to support stack layouts.
-** XXX ought to use a MR_Entry_Stack_Layout and MR_Cont_Stack_Layout
-** struct to make it easier to access the fields.
+** Structs and macros to support stack layouts.
 */
 
+typedef	struct MR_stack_layout_shape_struct {
+	Word			*MR_stack_layout_shape_type;
+	Word			MR_stack_layout_shape_inst;
+} MR_stack_layout_shape;
+
+typedef	struct MR_stack_layout_var_struct {
+	Integer			MR_stack_layout_locn;
+	MR_stack_layout_shape	*MR_stack_layout_shape;
+} MR_stack_layout_var;
+
+typedef	struct MR_stack_layout_vars_struct {
+	MR_stack_layout_var	*MR_stack_layout_pairs;
+	String			*MR_stack_layout_names;
+	Word			*MR_stack_layout_tvars;
+} MR_stack_layout_vars;
+
+typedef	struct MR_stack_layout_entry_struct {
+	Code			*MR_stack_layout_code_addr;
+	MR_Determinism		MR_stack_layout_detism;
+	Integer			MR_stack_layout_stack_slots;
+	MR_Live_Lval		MR_stack_layout_succip_locn;
+	/* the fields from here onwards are present only with procid layouts */
+	MR_PredFunc		MR_stack_layout_pred_or_func;
+	String			MR_stack_layout_decl_module;
+	String			MR_stack_layout_def_module;
+	String			MR_stack_layout_name;
+	Integer			MR_stack_layout_arity;
+	Integer			MR_stack_layout_mode;
+	/* the fields from here onwards are present only with trace layouts */
+	Integer			MR_stack_layout_in_arg_count;
+	MR_stack_layout_vars	MR_stack_layout_in_arg_info;
+	Integer			MR_stack_layout_out_arg_count;
+	MR_stack_layout_vars	MR_stack_layout_out_arg_info;
+} MR_stack_layout_entry;
+
+/* The following macros support obsolete code. */
 #define MR_ENTRY_STACK_LAYOUT_GET_LABEL_ADDRESS(s)		\
 		((Code *) field(0, (s), 0))
 
@@ -221,10 +284,10 @@
 		(field(0, (s), 0))
 
 #define MR_ENTRY_STACK_LAYOUT_GET_NUM_SLOTS(s)			\
-		(field(0, (s), 1))
+		(field(0, (s), 2))
 
 #define MR_ENTRY_STACK_LAYOUT_GET_CODE_MODEL(s)			\
-		(field(0, (s), 2))
+		(field(0, (s), 1) & 1)
 
 #define MR_ENTRY_STACK_LAYOUT_GET_SUCCIP_LOC(s)			\
 		(field(0, (s), 3))
Index: runtime/mercury_init.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_init.h,v
retrieving revision 1.2
diff -u -u -r1.2 mercury_init.h
--- mercury_init.h	1997/11/23 07:21:25	1.2
+++ mercury_init.h	1998/02/02 04:27:11
@@ -96,6 +96,7 @@
 extern	void	mercury_init_io(void);		/* in the Mercury library */
 extern	void	ML_io_init_state(void);		/* in the Mercury library */
 extern	void	ML_io_finalize_state(void);	/* in the Mercury library */
+extern	void	ML_io_print(Word, Word);	/* in the Mercury library */
 
 #endif /* not MERCURY_INIT_H */
 
Index: runtime/mercury_string.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_string.h,v
retrieving revision 1.7
diff -u -u -r1.7 mercury_string.h
--- mercury_string.h	1997/11/23 07:21:36	1.7
+++ mercury_string.h	1998/02/02 06:32:34
@@ -13,7 +13,6 @@
 
 #include "mercury_heap.h"	/* for incr_hp_atomic */
 
-
 /*
 ** Mercury characters are given type `Char', which is a typedef for `char'.
 ** But BEWARE: when stored in an Integer, the value must be
@@ -22,12 +21,16 @@
 **
 ** We may eventually move to using wchar_t for Mercury characters and strings,
 ** so it is important to use these typedefs.
+**
+** The actual typedefs are in mercury_types.h to avoid problems with
+** circular #includes.
+**
+** typedef char Char;
+** typedef unsigned char UnsignedChar;
+**
+** typedef Char *String;
+** typedef const Char *ConstString;
 */
-typedef char Char;
-typedef unsigned char UnsignedChar;
-
-typedef Char *String;
-typedef const Char *ConstString;
 
 /*
 ** string_const("...", len):
Index: runtime/mercury_trace.c
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_trace.c,v
retrieving revision 1.5
diff -u -u -r1.5 mercury_trace.c
--- mercury_trace.c	1998/01/25 08:22:49	1.5
+++ mercury_trace.c	1998/02/02 06:18:01
@@ -11,12 +11,13 @@
 ** "Opium: An extendable trace analyser for Prolog" by Mireille Ducasse,
 ** available from http://www.irisa.fr/lande/ducasse.
 **
-** Main author: Erwan Jahier.
-** Significant adaptations by Zoltan Somogyi.
+** Main authors: Erwan Jahier and Zoltan Somogyi.
 */
 
 #include "mercury_imp.h"
 #include "mercury_trace.h"
+#include "mercury_engine.h"
+#include "mercury_wrapper.h"
 #include <stdio.h>
 
 /*
@@ -71,11 +72,18 @@
 static	MR_trace_cmd_type	MR_trace_cmd = MR_CMD_NEXT;
 static	int			MR_trace_seqno = 0;
 
-void MR_trace_display(MR_trace_port port, MR_trace_code_model model, int seqno,
-	int depth, const char *modulename, const char *predname,
-	int arity, int modenum, const char *path);
-void MR_trace_interaction(MR_trace_port port, int seqno);
-void MR_trace_help(void);
+typedef	enum {
+	MR_INTERACT,
+	MR_NO_INTERACT
+} MR_trace_interact;
+
+void	MR_trace_display(MR_trace_interact interact,
+		const MR_stack_layout_entry *layout,
+		MR_trace_port port, int seqno, int depth, const char *path);
+void	MR_trace_browse(int var_count, const MR_stack_layout_vars *var_info);
+void	MR_trace_browse_var(char *name, const MR_stack_layout_var *var);
+int	MR_trace_get_cmd(void);
+void	MR_trace_help(void);
 
 #define	port_is_final(port)	(port == MR_PORT_EXIT || port == MR_PORT_FAIL)
 
@@ -85,36 +93,37 @@
 */
 
 void
-MR_trace(MR_trace_port port, MR_trace_code_model model, int seqno, int depth,
-	 const char *modulename, const char *predname, int arity, int modenum,
-	 const char *path)
+MR_trace(const Word *layout_word, MR_trace_port port,
+	int seqno, int depth, const char *path)
 {
+	const MR_stack_layout_entry	*layout;
+	MR_trace_interact		interact;
+
+	layout = (const MR_stack_layout_entry *) layout_word;
+
 	MR_trace_event_number++;
 	switch (MR_trace_cmd) {
 		case MR_CMD_NEXT:
-			MR_trace_display(port, model, seqno, depth, modulename,
-				predname, arity, modenum, path);
-			MR_trace_interaction(port, seqno);
+			MR_trace_display(MR_INTERACT, layout,
+				port, seqno, depth, path);
 			break;
 
 		case MR_CMD_JUMP:
-			MR_trace_display(port, model, seqno, depth,
-				modulename, predname, arity,
-				modenum, path);
-
 			if (MR_trace_seqno == seqno && port_is_final(port)) {
-				MR_trace_interaction(port, seqno);
+				interact = MR_INTERACT;
+			} else {
+				interact = MR_NO_INTERACT;
 			}
 
+			MR_trace_display(interact, layout,
+				port, seqno, depth, path);
+
 			break;
 
 		case MR_CMD_SKIP:
 			if (MR_trace_seqno == seqno && port_is_final(port)) {
-				MR_trace_display(port, model, seqno, depth,
-					modulename, predname, arity,
-					modenum, path);
-
-				MR_trace_interaction(port, seqno);
+				MR_trace_display(MR_INTERACT, layout,
+					port, seqno, depth, path);
 			}
 
 			break;
@@ -123,9 +132,8 @@
 			break;
 
 		case MR_CMD_DUMP:
-			MR_trace_display(port, model, seqno, depth,
-				modulename, predname, arity,
-				modenum, path);
+			MR_trace_display(MR_NO_INTERACT, layout,
+				port, seqno, depth, path);
 			break;
 
 		case MR_CMD_ABORT:
@@ -138,9 +146,9 @@
 	}
 }
 
-void MR_trace_display(MR_trace_port port, MR_trace_code_model model, int seqno,
-	int depth, const char *modulename, const char *predname,
-	int arity, int modenum, const char *path)
+void MR_trace_display(MR_trace_interact interact,
+	const MR_stack_layout_entry *layout,
+	MR_trace_port port, int seqno, int depth, const char *path)
 {
 	int	i;
 
@@ -184,83 +192,334 @@
 			fatal_error("MR_trace_display called with inappropriate port");
 	}
 
-	switch (model) {
-		case MR_MODEL_DET:
+	switch ((int) layout->MR_stack_layout_detism) {
+		case MR_DETISM_DET:
 			fprintf(stderr, "DET  ");
 			break;
 
-		case MR_MODEL_SEMI:
+		case MR_DETISM_SEMI:
 			fprintf(stderr, "SEMI ");
 			break;
 
-		case MR_MODEL_NON:
+		case MR_DETISM_NON:
 			fprintf(stderr, "NON  ");
 			break;
+
+		case MR_DETISM_MULTI:
+			fprintf(stderr, "MUL  ");
+			break;
+
+		case MR_DETISM_ERRONEOUS:
+			fprintf(stderr, "ERR  ");
+			break;
+
+		case MR_DETISM_FAILURE:
+			fprintf(stderr, "FAI  ");
+			break;
+
+		case MR_DETISM_CCNON:
+			fprintf(stderr, "CCN  ");
+			break;
+
+		case MR_DETISM_CCMULTI:
+			fprintf(stderr, "CCM  ");
+			break;
+		
+		default:
+			fprintf(stderr, "???  ");
+			break;
 	}
 
-	fprintf(stderr, "%s:%s/%d-%d %s\n",
-		modulename, predname, arity, modenum, path);
+	/*
+	** The following should be a full identification of the procedure
+	** provided (a) there was no intermodule optimization and (b) we are
+	** not interested in tracing compiler-generated procedures.
+	*/
+
+	fprintf(stderr, "%s:%s/%ld-%ld %s\n",
+		layout->MR_stack_layout_def_module,
+		layout->MR_stack_layout_name,
+		(long) layout->MR_stack_layout_arity,
+		(long) layout->MR_stack_layout_mode,
+		path);
+
+	while (interact == MR_INTERACT) {
+		fprintf(stderr, "mtrace> ");
+
+		switch (MR_trace_get_cmd()) {
+			case 'n':
+			case '\n':
+				MR_trace_cmd = MR_CMD_NEXT;
+				break;
+
+			case 'c':
+				MR_trace_cmd = MR_CMD_CONT;
+				break;
+
+			case 'd':
+				MR_trace_cmd = MR_CMD_DUMP;
+				break;
+
+			case 'j':
+				if (port_is_final(port)) {
+					fprintf(stderr, "cannot jump from this port\n");
+					continue;
+				} else {
+					MR_trace_cmd = MR_CMD_JUMP;
+					MR_trace_seqno = seqno;
+				}
+
+				break;
+
+			case 'p':
+				if (port == MR_PORT_CALL) {
+					MR_trace_browse((int) layout->MR_stack_layout_in_arg_count, &layout->MR_stack_layout_in_arg_info);
+				} else if (port == MR_PORT_EXIT) {
+					MR_trace_browse((int) layout->MR_stack_layout_out_arg_count, &layout->MR_stack_layout_out_arg_info);
+				} else {
+					fprintf(stderr, "cannot print from this port\n");
+				}
+
+				continue;
+
+			case 's':
+				if (port_is_final(port)) {
+					fprintf(stderr, "cannot skip from this port\n");
+					continue;
+				} else {
+					MR_trace_cmd = MR_CMD_SKIP;
+					MR_trace_seqno = seqno;
+				}
+
+				break;
+
+			case EOF:
+			case 'a':
+				fprintf(stderr, "are you sure you want to abort? ");
+				if (MR_trace_get_cmd() == 'y') {
+					MR_trace_cmd = MR_CMD_ABORT;
+					break;
+				} else {
+					continue;
+				}
+
+			default:
+				MR_trace_help();
+				continue;
+		}
+
+		interact = MR_NO_INTERACT;
+	}
 }
 
+typedef struct {
+	Word	*saved_succip;
+	Word	*saved_hp;
+	Word	*saved_sp;
+	Word	*saved_curfr;
+	Word	*saved_maxfr;
+} MR_ctrl_regs;
+
+static	MR_ctrl_regs	saved_ctrl;
+static	Word		saved_rs[10];
+
+void	MR_copy_regs_to_save_area(void);
+void	MR_copy_regs_from_save_area(void);
+
 void
-MR_trace_interaction(MR_trace_port port, int seqno)
+MR_copy_regs_to_save_area(void)
 {
-	int	cmd;
-	int	c;
+	saved_ctrl.saved_succip = succip;
+	saved_ctrl.saved_hp     = hp;
+	saved_ctrl.saved_sp     = sp;
+	saved_ctrl.saved_curfr  = curfr;
+	saved_ctrl.saved_maxfr  = maxfr;
+
+	saved_rs[0] = r1;
+	saved_rs[1] = r2;
+	saved_rs[2] = r3;
+	saved_rs[3] = r4;
+	saved_rs[4] = r5;
+	saved_rs[5] = r6;
+	saved_rs[6] = r7;
+	saved_rs[7] = r8;
+	saved_rs[8] = r9;
+	saved_rs[9] = r10;
+}
 
-	fprintf(stderr, "trace command [a|c|d|j|n|s] ");
+void
+MR_copy_regs_from_save_area(void)
+{
+	succip = saved_ctrl.saved_succip;
+	hp     = saved_ctrl.saved_hp;
+	sp     = saved_ctrl.saved_sp;
+	curfr  = saved_ctrl.saved_curfr;
+	maxfr  = saved_ctrl.saved_maxfr;
+
+	r1  = saved_rs[0];
+	r2  = saved_rs[1];
+	r3  = saved_rs[2];
+	r4  = saved_rs[3];
+	r5  = saved_rs[4];
+	r6  = saved_rs[5];
+	r7  = saved_rs[6];
+	r8  = saved_rs[7];
+	r9  = saved_rs[8];
+	r10 = saved_rs[9];
+}
 
-	cmd = getchar();	/* read the trace command */
+void
+MR_trace_browse(int var_count, const MR_stack_layout_vars *vars)
+{
+	int	i;
+	char	*name;
 
-	/* skip the rest of the line */
-	c = cmd;
-	while (c != EOF && c != '\n')
-		c = getchar();
+	if (var_count == 0) {
+		printf("no live variables\n");
+		return;
+	}
+
+	/*
+	** In the process of browsing, we call Mercury code,
+	** which may clobber the contents of the control registers
+	** and the contents of the gp registers up to r<maxreg>.
+	** We must therefore save and restore these.
+	** XXX The value of maxreg ought to be given to us by the compiler
+	** through a parameter to MR_trace; for the time being, we use 10.
+	*/
+
+	MR_copy_regs_to_save_area();
+	for (i = 0; i < var_count; i++) {
+		if (vars->MR_stack_layout_names != NULL &&
+				vars->MR_stack_layout_names[i] != NULL)
+			name = vars->MR_stack_layout_names[i];
+		else
+			name = NULL;
 
-	switch (cmd) {
-		case 'n':
-		case '\n':
-			MR_trace_cmd = MR_CMD_NEXT;
+		MR_trace_browse_var(name, &vars->MR_stack_layout_pairs[i]);
+	}
+
+	MR_copy_regs_from_save_area();
+}
+
+/* if you want to debug this code, you may want to set this var to 1 */
+static	int	MR_trace_print_locn = 0;
+
+void
+MR_trace_browse_var(char *name, const MR_stack_layout_var *var)
+{
+	Integer			locn;
+	Word			value;
+	int			print_value;
+	int			locn_num;
+
+	/* The initial blanks are to visually separate */
+	/* the variable names from the prompt. */
+
+	if (name != NULL)
+		printf("%10s%-21s\t", "", name);
+	else
+		printf("%10s%-21s\t", "", "anonymous variable");
+
+	value = 0; /* not used; this shuts up a compiler warning */
+	print_value = FALSE;
+
+	locn = var->MR_stack_layout_locn;
+	locn_num = (int) MR_LIVE_LVAL_NUMBER(locn);
+	switch (MR_LIVE_LVAL_TYPE(locn)) {
+		case MR_LVAL_TYPE_R:
+			if (MR_trace_print_locn)
+				printf("r%d", locn_num);
+			value = saved_rs[locn_num - 1];
+			print_value = TRUE;
 			break;
 
-		case 'c':
-			MR_trace_cmd = MR_CMD_CONT;
+		case MR_LVAL_TYPE_F:
+			if (MR_trace_print_locn)
+				printf("f%d", locn_num);
 			break;
 
-		case 'd':
-			MR_trace_cmd = MR_CMD_DUMP;
+		case MR_LVAL_TYPE_STACKVAR:
+			if (MR_trace_print_locn)
+				printf("stackvar%d", locn_num);
+			value = detstackvar(locn_num);
+			print_value = TRUE;
 			break;
 
-		case 'j':
-			if (port_is_final(port)) {
-				fprintf(stderr, "cannot jump from this port\n");
-				MR_trace_interaction(port, seqno);
-			} else {
-				MR_trace_cmd = MR_CMD_JUMP;
-				MR_trace_seqno = seqno;
-			}
+		case MR_LVAL_TYPE_FRAMEVAR:
+			if (MR_trace_print_locn)
+				printf("framevar%d", locn_num);
+			value = framevar(locn_num);
+			print_value = TRUE;
+			break;
 
+		case MR_LVAL_TYPE_SUCCIP:
+			if (MR_trace_print_locn)
+				printf("succip");
 			break;
 
-		case 's':
-			if (port_is_final(port)) {
-				fprintf(stderr, "cannot skip from this port\n");
-				MR_trace_interaction(port, seqno);
-			} else {
-				MR_trace_cmd = MR_CMD_SKIP;
-				MR_trace_seqno = seqno;
-			}
+		case MR_LVAL_TYPE_MAXFR:
+			if (MR_trace_print_locn)
+				printf("maxfr");
+			break;
+
+		case MR_LVAL_TYPE_CURFR:
+			if (MR_trace_print_locn)
+				printf("curfr");
+			break;
 
+		case MR_LVAL_TYPE_HP:
+			if (MR_trace_print_locn)
+				printf("hp");
 			break;
 
-		case 'a':
-			MR_trace_cmd = MR_CMD_ABORT;
+		case MR_LVAL_TYPE_SP:
+			if (MR_trace_print_locn)
+				printf("sp");
+			break;
+
+		case MR_LVAL_TYPE_UNKNOWN:
+			if (MR_trace_print_locn)
+				printf("unknown");
 			break;
 
 		default:
-			MR_trace_help();
-			MR_trace_interaction(port, seqno);
+			if (MR_trace_print_locn)
+				printf("DEFAULT");
+			break;
+	}
+
+	if (print_value) {
+		MR_stack_layout_shape	*shape;
+		const Word		*type;
+
+		printf("\t");
+
+		shape = var->MR_stack_layout_shape;
+		type  = shape->MR_stack_layout_shape_type;
+		/* (*MR_library_trace_browser)((Word) type, (Word) value); */
+		r1 = (Word) type;
+		r2 = (Word) value;
+		call_engine(MR_library_trace_browser);
 	}
+
+	printf("\n");
+}
+
+int
+MR_trace_get_cmd(void)
+{
+	int	cmd;
+	int	c;
+
+	cmd = getchar();	/* read the trace command */
+
+	/* skip the rest of the line */
+	c = cmd;
+	while (c != EOF && c != '\n')
+		c = getchar();
+
+	return cmd;
 }
 
 void
@@ -273,4 +532,5 @@
 	fprintf(stderr, " n: go to the next trace event.\n");
 	fprintf(stderr, " s: skip the current call, not printing trace.\n");
 	fprintf(stderr, " j: jump to end of current call, printing trace.\n");
+	fprintf(stderr, " p: print the variables live at this point.\n");
 }
Index: runtime/mercury_trace.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_trace.h,v
retrieving revision 1.4
diff -u -u -r1.4 mercury_trace.h
--- mercury_trace.h	1997/12/24 05:07:36	1.4
+++ mercury_trace.h	1998/01/30 06:10:14
@@ -28,19 +28,11 @@
 	MR_PORT_THEN, MR_PORT_ELSE, MR_PORT_DISJ, MR_PORT_SWITCH
 } MR_trace_port;
 
-typedef	enum {
-	MR_MODEL_DET, MR_MODEL_SEMI, MR_MODEL_NON
-} MR_trace_code_model;
-
 extern	void	MR_trace(
+	const Word *,		/* pointer to stack layout info */
 	MR_trace_port,
-	MR_trace_code_model,
 	int,			/* call sequence number */
 	int,			/* call depth */
-	const char *,		/* module name */
-	const char *,		/* predicate name */
-	int,			/* predicate arity */
-	int,			/* mode number within predicate */
 	const char *);		/* path to event goal within procedure */
 
 #endif /* MERCURY_TRACE_H */
Index: runtime/mercury_types.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_types.h,v
retrieving revision 1.7
diff -u -u -r1.7 mercury_types.h
--- mercury_types.h	1997/11/23 07:21:43	1.7
+++ mercury_types.h	1998/02/02 04:00:59
@@ -39,6 +39,15 @@
 	#error	For Mercury bytecode, we require 64-bit IEEE-754 floating point
 #endif
 
+/* The following four typedefs logically belong in mercury_string.h.     */
+/* They are defined here to avoid problems with circular #includes.      */
+/* If you modify them, you will need to modify mercury_string.h as well. */
+
+typedef char Char;
+typedef unsigned char UnsignedChar;
+
+typedef Char *String;
+typedef const Char *ConstString;
 
 /* continuation function type, for --high-level-C option */
 typedef void (*Cont) (void);
Index: runtime/mercury_wrapper.c
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_wrapper.c,v
retrieving revision 1.5
diff -u -u -r1.5 mercury_wrapper.c
--- mercury_wrapper.c	1998/01/06 07:06:06	1.5
+++ mercury_wrapper.c	1998/02/02 06:34:36
@@ -127,7 +127,8 @@
 		/* normally ML_io_init_state (io__init_state/2)*/
 void	(*MR_library_finalizer)(void);
 		/* normally ML_io_finalize_state (io__finalize_state/2) */
-
+Code	*MR_library_trace_browser;
+		/* normally mercury__io__print_3_0 (io__print/3) */
 
 #ifdef USE_GCC_NONLOCAL_GOTOS
 
Index: runtime/mercury_wrapper.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_wrapper.h,v
retrieving revision 1.4
diff -u -u -r1.4 mercury_wrapper.h
--- mercury_wrapper.h	1997/12/05 15:56:52	1.4
+++ mercury_wrapper.h	1998/02/02 06:34:48
@@ -44,6 +44,7 @@
 
 extern	void		(*MR_library_initializer)(void);
 extern	void		(*MR_library_finalizer)(void);
+extern	Code		*MR_library_trace_browser;
 
 extern	void		(*address_of_mercury_init_io)(void);
 extern	void		(*address_of_init_modules)(void);
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/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/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
Index: tests/misc_tests/debugger_test.exp
===================================================================
RCS file: /home/mercury1/repository/tests/misc_tests/debugger_test.exp,v
retrieving revision 1.1
diff -u -u -r1.1 debugger_test.exp
--- debugger_test.exp	1998/01/25 08:44:32	1.1
+++ debugger_test.exp	1998/02/02 06:27:08
@@ -1,100 +1,108 @@
        1:      1  1  CALL DET  debugger_test:main/2-0 
-trace command [a|c|d|j|n|s] valid commands are:
+mtrace> valid commands are:
  a: abort the current execution.
  c: continue to end, not printing the trace.
  d: continue to end, printing the trace.
  n: go to the next trace event.
  s: skip the current call, not printing trace.
  j: jump to end of current call, printing trace.
-trace command [a|c|d|j|n|s] Pure Prolog Interpreter.
+ p: print the variables live at this point.
+mtrace> Pure Prolog Interpreter.
 
        2:      1  1  ELSE DET  debugger_test:main/2-0 c4;e;
-trace command [a|c|d|j|n|s]        3:      2  2   CALL DET  debugger_test:database_init/1-0 
-trace command [a|c|d|j|n|s]        4:      2  2   EXIT DET  debugger_test:database_init/1-0 
-trace command [a|c|d|j|n|s]        5:      3  2   CALL DET  debugger_test:consult_list/5-0 
-trace command [a|c|d|j|n|s]        6:      3  2   SWTC DET  debugger_test:consult_list/5-0 s1;
-trace command [a|c|d|j|n|s]        7:      4  3    CALL DET  debugger_test:consult/5-0 
-trace command [a|c|d|j|n|s] Consulting file `debugger_test.m'...
+mtrace>        3:      2  2   CALL DET  debugger_test:database_init/1-0 
+mtrace>        4:      2  2   EXIT DET  debugger_test:database_init/1-0 
+mtrace>        5:      3  2   CALL DET  debugger_test:consult_list/5-0 
+mtrace>        6:      3  2   SWTC DET  debugger_test:consult_list/5-0 s1;
+mtrace>        7:      4  3    CALL DET  debugger_test:consult/5-0 
+mtrace> Consulting file `debugger_test.m'...
        8:      4  3    THEN DET  debugger_test:consult/5-0 c7;t;
-trace command [a|c|d|j|n|s]        9:      5  4     CALL DET  debugger_test:consult_until_eof/4-0 
-trace command [a|c|d|j|n|s]       10:      6  5      CALL DET  debugger_test:consult_until_eof_2/5-0 
-trace command [a|c|d|j|n|s]       11:      6  5      SWTC DET  debugger_test:consult_until_eof_2/5-0 s3;
-trace command [a|c|d|j|n|s]       12:      7  6       CALL DET  debugger_test:database_assert_clause/4-0 
-trace command [a|c|d|j|n|s]       13:      7  6       ELSE DET  debugger_test:database_assert_clause/4-0 e;
-trace command [a|c|d|j|n|s]       14:      7  6       EXIT DET  debugger_test:database_assert_clause/4-0 
-trace command [a|c|d|j|n|s]       15:      8  6       CALL DET  debugger_test:consult_until_eof/4-0 
-trace command [a|c|d|j|n|s]       16:      9  7        CALL DET  debugger_test:consult_until_eof_2/5-0 
-trace command [a|c|d|j|n|s]       17:      9  7        SWTC DET  debugger_test:consult_until_eof_2/5-0 s3;
-trace command [a|c|d|j|n|s]       18:     10  8         CALL DET  debugger_test:database_assert_clause/4-0 
-trace command [a|c|d|j|n|s]       19:     10  8         ELSE DET  debugger_test:database_assert_clause/4-0 e;
-trace command [a|c|d|j|n|s]       20:     10  8         EXIT DET  debugger_test:database_assert_clause/4-0 
-trace command [a|c|d|j|n|s]       21:     11  8         CALL DET  debugger_test:consult_until_eof/4-0 
-trace command [a|c|d|j|n|s]      681:     11  8         EXIT DET  debugger_test:consult_until_eof/4-0 
-trace command [a|c|d|j|n|s]      682:      9  7        EXIT DET  debugger_test:consult_until_eof_2/5-0 
-trace command [a|c|d|j|n|s]      683:      8  6       EXIT DET  debugger_test:consult_until_eof/4-0 
-trace command [a|c|d|j|n|s] valid commands are:
+mtrace>        9:      5  4     CALL DET  debugger_test:consult_until_eof/4-0 
+mtrace>       10:      6  5      CALL DET  debugger_test:consult_until_eof_2/5-0 
+mtrace>       11:      6  5      SWTC DET  debugger_test:consult_until_eof_2/5-0 s3;
+mtrace>       12:      7  6       CALL DET  debugger_test:database_assert_clause/4-0 
+mtrace>       13:      7  6       ELSE DET  debugger_test:database_assert_clause/4-0 e;
+mtrace>       14:      7  6       EXIT DET  debugger_test:database_assert_clause/4-0 
+mtrace> mtrace>           HeadVar__4           		[clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("module"), [functor(atom("interpreter"), [], context("debugger_test.m", 22))], context("debugger_test.m", 22))], context("debugger_test.m", 22)), functor(atom("true"), [], context("", 0)))]
+      15:      8  6       CALL DET  debugger_test:consult_until_eof/4-0 
+mtrace>       16:      9  7        CALL DET  debugger_test:consult_until_eof_2/5-0 
+mtrace>       17:      9  7        SWTC DET  debugger_test:consult_until_eof_2/5-0 s3;
+mtrace>       18:     10  8         CALL DET  debugger_test:database_assert_clause/4-0 
+mtrace>       19:     10  8         ELSE DET  debugger_test:database_assert_clause/4-0 e;
+mtrace>       20:     10  8         EXIT DET  debugger_test:database_assert_clause/4-0 
+mtrace>       21:     11  8         CALL DET  debugger_test:consult_until_eof/4-0 
+mtrace> mtrace>           HeadVar__1           		[clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("interface"), [], context("debugger_test.m", 23))], context("debugger_test.m", 23)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("module"), [functor(atom("interpreter"), [], context("debugger_test.m", 22))], context("debugger_test.m", 22))], context("debugger_test.m", 22)), functor(atom("true"), [], context("", 0)))]
+          HeadVar__3           		state(<<c_pointer>>)
+     681:     11  8         EXIT DET  debugger_test:consult_until_eof/4-0 
+mtrace>      682:      9  7        EXIT DET  debugger_test:consult_until_eof_2/5-0 
+mtrace>      683:      8  6       EXIT DET  debugger_test:consult_until_eof/4-0 
+mtrace> valid commands are:
  a: abort the current execution.
  c: continue to end, not printing the trace.
  d: continue to end, printing the trace.
  n: go to the next trace event.
  s: skip the current call, not printing trace.
  j: jump to end of current call, printing trace.
-trace command [a|c|d|j|n|s]      684:      6  5      EXIT DET  debugger_test:consult_until_eof_2/5-0 
-trace command [a|c|d|j|n|s]      685:      5  4     EXIT DET  debugger_test:consult_until_eof/4-0 
-trace command [a|c|d|j|n|s]      686:      4  3    EXIT DET  debugger_test:consult/5-0 
-trace command [a|c|d|j|n|s]      687:    259  3    CALL DET  debugger_test:consult_list/5-0 
-trace command [a|c|d|j|n|s]      688:    259  3    SWTC DET  debugger_test:consult_list/5-0 s2;
+ p: print the variables live at this point.
+mtrace>      684:      6  5      EXIT DET  debugger_test:consult_until_eof_2/5-0 
+mtrace>      685:      5  4     EXIT DET  debugger_test:consult_until_eof/4-0 
+mtrace>      686:      4  3    EXIT DET  debugger_test:consult/5-0 
+mtrace>      687:    259  3    CALL DET  debugger_test:consult_list/5-0 
+mtrace>      688:    259  3    SWTC DET  debugger_test:consult_list/5-0 s2;
      689:    259  3    EXIT DET  debugger_test:consult_list/5-0 
-trace command [a|c|d|j|n|s]      690:      3  2   EXIT DET  debugger_test:consult_list/5-0 
-trace command [a|c|d|j|n|s]      691:    260  2   CALL DET  debugger_test:main_loop/3-0 
-trace command [a|c|d|j|n|s] ?-      692:    261  3    CALL DET  debugger_test:main_loop_2/4-0 
-trace command [a|c|d|j|n|s]      693:    261  3    SWTC DET  debugger_test:main_loop_2/4-0 s3;
-trace command [a|c|d|j|n|s]      694:    262  4     CALL NON  debugger_test:solve/4-0 
-trace command [a|c|d|j|n|s]      695:    262  4     DISJ NON  debugger_test:solve/4-0 d1;
-trace command [a|c|d|j|n|s]      696:    262  4     DISJ NON  debugger_test:solve/4-0 d2;
-trace command [a|c|d|j|n|s]      697:    262  4     DISJ NON  debugger_test:solve/4-0 d3;
-trace command [a|c|d|j|n|s]      698:    262  4     DISJ NON  debugger_test:solve/4-0 d4;
-trace command [a|c|d|j|n|s]      699:    263  5      CALL SEMI debugger_test:unify/4-0 
-trace command [a|c|d|j|n|s]      700:    263  5      SWTC SEMI debugger_test:unify/4-0 s2;
+mtrace>      690:      3  2   EXIT DET  debugger_test:consult_list/5-0 
+mtrace>      691:    260  2   CALL DET  debugger_test:main_loop/3-0 
+mtrace>           HeadVar__1           		[clause(varset(6, three(2, "_Goal", 4, "Head", two(1, "Database", empty, empty), two(3, "VarSet", empty, empty), three(5, "Body", 6, "Clause", empty, empty, empty)), empty), functor(atom("database_lookup_clause"), [variable(1), variable(2), variable(3), variable(4), variable(5)], context("debugger_test.m", 369)), functor(atom(","), [functor(atom("list__member"), [variable(6), variable(1)], context("debugger_test.m", 370)), functor(atom("="), [variable(6), functor(atom("clause"), [variable(3), variable(4), variable(5)], context("debugger_test.m", 371))], context("debugger_test.m", 371))], context("debugger_test.m", 370))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("mode"), [functor(atom("is"), [functor(atom("database_lookup_clause"), [functor(atom("in"), [], context("debugger_test.m", 367)), functor(atom("in"), [], context("debugger_test.m", 367)), functor(atom("out"), [], context("debugger_test.m", 367)), functor(atom("out"), [], context("debugger_test.m", 367)), functor(atom("out"), [], context("debugger_test.m", 367))], context("debugger_test.m", 367)), functor(atom("nondet"), [], context("debugger_test.m", 367))], context("debugger_test.m", 367))], context("debugger_test.m", 367))], context("debugger_test.m", 367)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("pred"), [functor(atom("database_lookup_clause"), [functor(atom("database"), [], context("debugger_test.m", 366)), functor(atom("term"), [], context("debugger_test.m", 366)), functor(atom("varset"), [], context("debugger_test.m", 366)), functor(atom("term"), [], context("debugger_test.m", 366)), functor(atom("term"), [], context("debugger_test.m", 366))], context("debugger_test.m", 366))], context("debugger_test.m", 366))], context("debugger_test.m", 366)), functor(atom("true"), [], context("", 0))), clause(varset(10, two(4, "Clause", two(2, "VarSet", two(1, "Database", empty, empty), two(3, "Term", empty, empty)), two(6, "B", two(5, "H", empty, empty), four(8, "Head", 9, "Body", 10, "Context", empty, empty, empty, empty))), empty), functor(atom("database_assert_clause"), [variable(1), variable(2), variable(3), functor(atom("."), [variable(4), variable(1)], context("debugger_test.m", 355))], context("debugger_test.m", 355)), functor(atom(","), [functor(atom(";"), [functor(atom("->"), [functor(atom("="), [variable(3), functor(atom("term__functor"), [functor(atom("term__atom"), [functor(string(":-"), [], context("debugger_test.m", 356))], context("debugger_test.m", 356)), functor(atom("."), [variable(5), functor(atom("."), [variable(6), functor(atom("[]"), [], context("debugger_test.m", 356))], context("debugger_test.m", 356))], context("debugger_test.m", 356)), variable(7)], context("debugger_test.m", 356))], context("debugger_test.m", 356)), functor(atom(","), [functor(atom("="), [variable(8), variable(5)], context("debugger_test.m", 357)), functor(atom("="), [variable(9), variable(6)], context("debugger_test.m", 358))], context("debugger_test.m", 357))], context("debugger_test.m", 356)), functor(atom(","), [functor(atom("="), [variable(8), variable(3)], context("debugger_test.m", 360)), functor(atom(","), [functor(atom("term__context_init"), [variable(10)], context("debugger_test.m", 361)), functor(atom("="), [variable(9), functor(atom("term__functor"), [functor(atom("term__atom"), [functor(string("true"), [], context("debugger_test.m", 362))], context("debugger_test.m", 362)), functor(atom("[]"), [], context("debugger_test.m", 362)), variable(10)], context("debugger_test.m", 362))], context("debugger_test.m", 362))], context("debugger_test.m", 361))], context("debugger_test.m", 360))], context("debugger_test.m", 359)), functor(atom("="), [variable(4), functor(atom("clause"), [variable(2), variable(8), variable(9)], context("debugger_test.m", 364))], context("debugger_test.m", 364))], context("debugger_test.m", 363))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("mode"), [functor(atom("is"), [functor(atom("database_assert_clause"), [functor(atom("in"), [], context("debugger_test.m", 353)), functor(atom("in"), [], context("debugger_test.m", 353)), functor(atom("in"), [], context("debugger_test.m", 353)), functor(atom("out"), [], context("debugger_test.m", 353))], context("debugger_test.m", 353)), functor(atom("det"), [], context("debugger_test.m", 353))], context("debugger_test.m", 353))], context("debugger_test.m", 353))], context("debugger_test.m", 353)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("pred"), [functor(atom("database_assert_clause"), [functor(atom("database"), [], context("debugger_test.m", 352)), functor(atom("varset"), [], context("debugger_test.m", 352)), functor(atom("term"), [], context("debugger_test.m", 352)), functor(atom("database"), [], context("debugger_test.m", 352))], context("debugger_test.m", 352))], context("debugger_test.m", 352))], context("debugger_test.m", 352)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom("database_init"), [functor(atom("[]"), [], context("debugger_test.m", 350))], context("debugger_test.m", 350)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("mode"), [functor(atom("is"), [functor(atom("database_init"), [functor(atom("out"), [], context("debugger_test.m", 348))], context("debugger_test.m", 348)), functor(atom("det"), [], context("debugger_test.m", 348))], context("debugger_test.m", 348))], context("debugger_test.m", 348))], context("debugger_test.m", 348)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("pred"), [functor(atom("database_init"), [functor(atom("database"), [], context("debugger_test.m", 347))], context("debugger_test.m", 347))], context("debugger_test.m", 347))], context("debugger_test.m", 347)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("type"), [functor(atom("--->"), [functor(atom("clause"), [], context("debugger_test.m", 345)), functor(atom("clause"), [functor(atom("varset"), [], context("debugger_test.m", 345)), functor(atom("term"), [], context("debugger_test.m", 345)), functor(atom("term"), [], context("debugger_test.m", 345))], context("debugger_test.m", 345))], context("debugger_test.m", 345))], context("debugger_test.m", 345))], context("debugger_test.m", 345)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("type"), [functor(atom("=="), [functor(atom("database"), [], context("debugger_test.m", 344)), functor(atom("list"), [functor(atom("clause"), [], context("debugger_test.m", 344))], context("debugger_test.m", 344))], context("debugger_test.m", 344))], context("debugger_test.m", 344))], context("debugger_test.m", 344)), functor(atom("true"), [], context("", 0))), clause(varset(5, two(2, "Terms0", two(1, "Term0", empty, empty), four(3, "VarSet", 4, "Term", 5, "Terms", empty, empty, empty, empty)), empty), functor(atom("apply_rec_substitution_to_list"), [functor(atom("."), [variable(1), variable(2)], context("debugger_test.m", 333)), variable(3), functor(atom("."), [variable(4), variable(5)], context("debugger_test.m", 334))], context("debugger_test.m", 333)), functor(atom(","), [functor(atom("apply_rec_substitution"), [variable(1), variable(3), variable(4)], context("debugger_test.m", 335)), functor(atom("apply_rec_substitution_to_list"), [variable(2), variable(3), variable(5)], context("debugger_test.m", 336))], context("debugger_test.m", 335))), clause(varset(1, two(1, "_VarSet", empty, empty), empty), functor(atom("apply_rec_substitution_to_list"), [functor(atom("[]"), [], context("debugger_test.m", 332)), variable(1), functor(atom("[]"), [], context("debugger_test.m", 332))], context("debugger_test.m", 332)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("mode"), [functor(atom("is"), [functor(atom("apply_rec_substitution_to_list"), [functor(atom("in"), [], context("debugger_test.m", 330)), functor(atom("in"), [], context("debugger_test.m", 330)), functor(atom("out"), [], context("debugger_test.m", 330))], context("debugger_test.m", 330)), functor(atom("det"), [], context("debugger_test.m", 330))], context("debugger_test.m", 330))], context("debugger_test.m", 330))], context("debugger_test.m", 330)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("pred"), [functor(atom("apply_rec_substitution_to_list"), [functor(atom("list"), [functor(atom("term"), [], context("debugger_test.m", 329))], context("debugger_test.m", 329)), functor(atom("varset"), [], context("debugger_test.m", 329)), functor(atom("list"), [functor(atom("term"), [], context("debugger_test.m", 329))], context("debugger_test.m", 329))], context("debugger_test.m", 329))], context("debugger_test.m", 329))], context("debugger_test.m", 329)), functor(atom("true"), [], context("", 0))), clause(varset(5, two(2, "Args0", two(1, "Name", empty, empty), four(3, "Context", 4, "VarSet", 5, "Args", empty, empty, empty, empty)), empty), functor(atom("apply_rec_substitution"), [functor(atom("term__functor"), [variable(1), variable(2), variable(3)], context("debugger_test.m", 325)), variable(4), functor(atom("term__functor"), [variable(1), variable(5), variable(3)], context("debugger_test.m", 326))], context("debugger_test.m", 325)), functor(atom("apply_rec_substitution_to_list"), [variable(2), variable(4), variable(5)], context("debugger_test.m", 327))), clause(varset(4, two(2, "VarSet", two(1, "Var", empty, empty), three(3, "Term", 4, "Replacement", empty, empty, empty)), empty), functor(atom("apply_rec_substitution"), [functor(atom("term__variable"), [variable(1)], context("debugger_test.m", 316)), variable(2), variable(3)], context("debugger_test.m", 316)), functor(atom(";"), [functor(atom("->"), [functor(atom("varset__search_var"), [variable(2), variable(1), variable(4)], context("debugger_test.m", 318)), functor(atom("apply_rec_substitution"), [variable(4), variable(2), variable(3)], context("debugger_test.m", 321))], context("debugger_test.m", 319)), functor(atom("="), [variable(3), functor(atom("term__variable"), [variable(1)], context("debugger_test.m", 323))], context("debugger_test.m", 323))], context("debugger_test.m", 322))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("mode"), [functor(atom("is"), [functor(atom("apply_rec_substitution"), [functor(atom("in"), [], context("debugger_test.m", 314)), functor(atom("in"), [], context("debugger_test.m", 314)), functor(atom("out"), [], context("debugger_test.m", 314))], context("debugger_test.m", 314)), functor(atom("det"), [], context("debugger_test.m", 314))], context("debugger_test.m", 314))], context("debugger_test.m", 314))], context("debugger_test.m", 314)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("pred"), [functor(atom("apply_rec_substitution"), [functor(atom("term"), [], context("debugger_test.m", 313)), functor(atom("varset"), [], context("debugger_test.m", 313)), functor(atom("term"), [], context("debugger_test.m", 313))], context("debugger_test.m", 313))], context("debugger_test.m", 313))], context("debugger_test.m", 313)), functor(atom("true"), [], context("", 0))), clause(varset(4, two(2, "Terms", two(1, "Term", empty, empty), three(3, "Y", 4, "VarSet", empty, empty, empty)), empty), functor(atom("occurs_list"), [functor(atom("."), [variable(1), variable(2)], context("debugger_test.m", 301)), variable(3), variable(4)], context("debugger_test.m", 301)), functor(atom(";"), [functor(atom("occurs"), [variable(1), variable(3), variable(4)], context("debugger_test.m", 302)), functor(atom("occurs_list"), [variable(2), variable(3), variable(4)], context("debugger_test.m", 304))], context("debugger_test.m", 303))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("mode"), [functor(atom("is"), [functor(atom("occurs_list"), [functor(atom("in"), [], context("debugger_test.m", 299)), functor(atom("in"), [], context("debugger_test.m", 299)), functor(atom("in"), [], context("debugger_test.m", 299))], context("debugger_test.m", 299)), functor(atom("semidet"), [], context("debugger_test.m", 299))], context("debugger_test.m", 299))], context("debugger_test.m", 299))], context("debugger_test.m", 299)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("pred"), [functor(atom("occurs_list"), [functor(atom("list"), [functor(atom("term"), [], context("debugger_test.m", 298))], context("debugger_test.m", 298)), functor(atom("var"), [], context("debugger_test.m", 298)), functor(atom("varset"), [], context("debugger_test.m", 298))], context("debugger_test.m", 298))], context("debugger_test.m", 298))], context("debugger_test.m", 298)), functor(atom("true"), [], context("", 0))), clause(varset(5, two(2, "As", two(1, "_F", empty, empty), three(4, "Y", 5, "VarSet", empty, empty, empty)), empty), functor(atom("occurs"), [functor(atom("term__functor"), [variable(1), variable(2), variable(3)], context("debugger_test.m", 295)), variable(4), variable(5)], context("debugger_test.m", 295)), functor(atom("occurs_list"), [variable(2), variable(4), variable(5)], context("debugger_test.m", 296))), clause(varset(4, two(2, "Y", two(1, "X", empty, empty), three(3, "VarSet", 4, "BindingOfX", empty, empty, empty)), empty), functor(atom("occurs"), [functor(atom("term__variable"), [variable(1)], context("debugger_test.m", 290)), variable(2), variable(3)], context("debugger_test.m", 290)), functor(atom(";"), [functor(atom("="), [variable(1), variable(2)], context("debugger_test.m", 291)), functor(atom(","), [functor(atom("varset__search_var"), [variable(3), variable(1), variable(4)], context("debugger_test.m", 293)), functor(atom("occurs"), [variable(4), variable(2), variable(3)], context("debugger_test.m", 294))], context("debugger_test.m", 293))], context("debugger_test.m", 292))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("mode"), [functor(atom("is"), [functor(atom("occurs"), [functor(atom("in"), [], context("debugger_test.m", 288)), functor(atom("in"), [], context("debugger_test.m", 288)), functor(atom("in"), [], context("debugger_test.m", 288))], context("debugger_test.m", 288)), functor(atom("semidet"), [], context("debugger_test.m", 288))], context("debugger_test.m", 288))], context("debugger_test.m", 288))], context("debugger_test.m", 288)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("pred"), [functor(atom("occurs"), [functor(atom("term"), [], context("debugger_test.m", 287)), functor(atom("var"), [], context("debugger_test.m", 287)), functor(atom("varset"), [], context("debugger_test.m", 287))], context("debugger_test.m", 287))], context("debugger_test.m", 287))], context("debugger_test.m", 287)), functor(atom("true"), [], context("", 0))), clause(varset(4, two(2, "Xs", two(1, "X", empty, empty), three(3, "Y", 4, "Ys", empty, empty, empty)), empty), functor(atom("-->"), [functor(atom("unify_list"), [functor(atom("."), [variable(1), variable(2)], context("debugger_test.m", 277)), functor(atom("."), [variable(3), variable(4)], context("debugger_test.m", 277))], context("debugger_test.m", 277)), functor(atom(","), [functor(atom("unify"), [variable(1), variable(3)], context("debugger_test.m", 278)), functor(atom("unify_list"), [variable(2), variable(4)], context("debugger_test.m", 279))], context("debugger_test.m", 278))], context("debugger_test.m", 277)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom("-->"), [functor(atom("unify_list"), [functor(atom("[]"), [], context("debugger_test.m", 276)), functor(atom("[]"), [], context("debugger_test.m", 276))], context("debugger_test.m", 276)), functor(atom("[]"), [], context("debugger_test.m", 276))], context("debugger_test.m", 276)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("mode"), [functor(atom("is"), [functor(atom("unify_list"), [functor(atom("in"), [], context("debugger_test.m", 274)), functor(atom("in"), [], context("debugger_test.m", 274)), functor(atom("in"), [], context("debugger_test.m", 274)), functor(atom("out"), [], context("debugger_test.m", 274))], context("debugger_test.m", 274)), functor(atom("semidet"), [], context("debugger_test.m", 274))], context("debugger_test.m", 274))], context("debugger_test.m", 274))], context("debugger_test.m", 274)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("pred"), [functor(atom("unify_list"), [functor(atom("list"), [functor(atom("term"), [], context("debugger_test.m", 273))], context("debugger_test.m", 273)), functor(atom("list"), [functor(atom("term"), [], context("debugger_test.m", 273))], context("debugger_test.m", 273)), functor(atom("varset"), [], context("debugger_test.m", 273)), functor(atom("varset"), [], context("debugger_test.m", 273))], context("debugger_test.m", 273))], context("debugger_test.m", 273))], context("debugger_test.m", 273)), functor(atom("true"), [], context("", 0))), clause(varset(5, four(1, "F", 2, "AsX", 4, "AsY", empty, empty, empty, empty), empty), functor(atom("-->"), [functor(atom("unify"), [functor(atom("term__functor"), [variable(1), variable(2), variable(3)], context("debugger_test.m", 270)), functor(atom("term__functor"), [variable(1), variable(4), variable(5)], context("debugger_test.m", 270))], context("debugger_test.m", 270)), functor(atom("unify_list"), [variable(2), variable(4)], context("debugger_test.m", 271))], context("debugger_test.m", 270)), functor(atom("true"), [], context("", 0))), clause(varset(7, three(2, "As", 4, "X", two(1, "F", empty, empty), two(3, "C", empty, empty), four(5, "VarSet0", 6, "VarSet", 7, "BindingOfX", empty, empty, empty, empty)), empty), functor(atom("unify"), [functor(atom("term__functor"), [variable(1), variable(2), variable(3)], context("debugger_test.m", 259)), functor(atom("term__variable"), [variable(4)], context("debugger_test.m", 259)), variable(5), variable(6)], context("debugger_test.m", 259)), functor(atom(";"), [functor(atom("->"), [functor(atom("varset__search_var"), [variable(5), variable(4), variable(7)], context("debugger_test.m", 261)), functor(atom("unify"), [functor(atom("term__functor"), [variable(1), variable(2), variable(3)], context("debugger_test.m", 263)), variable(7), variable(5), variable(6)], context("debugger_test.m", 263))], context("debugger_test.m", 262)), functor(atom(","), [functor(atom("\\+"), [functor(atom("occurs_list"), [variable(2), variable(4), variable(5)], context("debugger_test.m", 266))], context("debugger_test.m", 266)), functor(atom("varset__bind_var"), [variable(5), variable(4), functor(atom("term__functor"), [variable(1), variable(2), variable(3)], context("debugger_test.m", 267)), variable(6)], context("debugger_test.m", 267))], context("debugger_test.m", 266))], context("debugger_test.m", 265))), clause(varset(7, three(2, "F", 4, "C", two(1, "X", empty, empty), two(3, "As", empty, empty), four(5, "VarSet0", 6, "VarSet", 7, "BindingOfX", empty, empty, empty, empty)), empty), functor(atom("unify"), [functor(atom("term__variable"), [variable(1)], context("debugger_test.m", 248)), functor(atom("term__functor"), [variable(2), variable(3), variable(4)], context("debugger_test.m", 248)), variable(5), variable(6)], context("debugger_test.m", 248)), functor(atom(";"), [functor(atom("->"), [functor(atom("varset__search_var"), [variable(5), variable(1), variable(7)], context("debugger_test.m", 250)), functor(atom("unify"), [variable(7), functor(atom("term__functor"), [variable(2), variable(3), variable(4)], context("debugger_test.m", 252)), variable(5), variable(6)], context("debugger_test.m", 252))], context("debugger_test.m", 251)), functor(atom(","), [functor(atom("\\+"), [functor(atom("occurs_list"), [variable(3), variable(1), variable(5)], context("debugger_test.m", 255))], context("debugger_test.m", 255)), functor(atom("varset__bind_var"), [variable(5), variable(1), functor(atom("term__functor"), [variable(2), variable(3), variable(4)], context("debugger_test.m", 256)), variable(6)], context("debugger_test.m", 256))], context("debugger_test.m", 255))], context("debugger_test.m", 254))), clause(varset(9, two(4, "VarSet", two(2, "Y", two(1, "X", empty, empty), two(3, "VarSet0", empty, empty)), two(6, "BindingOfY", two(5, "BindingOfX", empty, empty), four(7, "SubstBindingOfX", 8, "BindingOfY2", 9, "SubstBindingOfY2", empty, empty, empty, empty))), empty), functor(atom("unify"), [functor(atom("term__variable"), [variable(1)], context("debugger_test.m", 200)), functor(atom("term__variable"), [variable(2)], context("debugger_test.m", 200)), variable(3), variable(4)], context("debugger_test.m", 200)), functor(atom(";"), [functor(atom("->"), [functor(atom("varset__search_var"), [variable(3), variable(1), variable(5)], context("debugger_test.m", 202)), functor(atom(";"), [functor(atom("->"), [functor(atom("varset__search_var"), [variable(3), variable(2), variable(6)], context("debugger_test.m", 205)), functor(atom("unify"), [variable(5), variable(6), variable(3), variable(4)], context("debugger_test.m", 209))], context("debugger_test.m", 206)), functor(atom(","), [functor(atom("apply_rec_substitution"), [variable(5), variable(3), variable(7)], context("debugger_test.m", 212)), functor(atom(";"), [functor(atom("->"), [functor(atom("="), [variable(7), functor(atom("term__variable"), [variable(2)], context("debugger_test.m", 214))], context("debugger_test.m", 214)), functor(atom("="), [variable(4), variable(3)], context("debugger_test.m", 215))], context("debugger_test.m", 214)), functor(atom(","), [functor(atom("\\+"), [functor(atom("occurs"), [variable(7), variable(2), variable(3)], context("debugger_test.m", 217))], context("debugger_test.m", 217)), functor(atom("varset__bind_var"), [variable(3), variable(2), variable(7), variable(4)], context("debugger_test.m", 218))], context("debugger_test.m", 217))], context("debugger_test.m", 216))], context("debugger_test.m", 213))], context("debugger_test.m", 210))], context("debugger_test.m", 203)), functor(atom(";"), [functor(atom("->"), [functor(atom("varset__search_var"), [variable(3), variable(2), variable(8)], context("debugger_test.m", 224)), functor(atom(","), [functor(atom("apply_rec_substitution"), [variable(8), variable(3), variable(9)], context("debugger_test.m", 227)), functor(atom(";"), [functor(atom("->"), [functor(atom("="), [variable(9), functor(atom("term__variable"), [variable(1)], context("debugger_test.m", 229))], context("debugger_test.m", 229)), functor(atom("="), [variable(4), variable(3)], context("debugger_test.m", 230))], context("debugger_test.m", 229)), functor(atom(","), [functor(atom("\\+"), [functor(atom("occurs"), [variable(9), variable(1), variable(3)], context("debugger_test.m", 232))], context("debugger_test.m", 232)), functor(atom("varset__bind_var"), [variable(3), variable(1), variable(9), variable(4)], context("debugger_test.m", 233))], context("debugger_test.m", 232))], context("debugger_test.m", 231))], context("debugger_test.m", 228))], context("debugger_test.m", 225)), functor(atom(";"), [functor(atom("->"), [functor(atom("="), [variable(1), variable(2)], context("debugger_test.m", 239)), functor(atom("="), [variable(4), variable(3)], context("debugger_test.m", 240))], context("debugger_test.m", 239)), functor(atom("varset__bind_var"), [variable(3), variable(1), functor(atom("term__variable"), [variable(2)], context("debugger_test.m", 242)), variable(4)], context("debugger_test.m", 242))], context("debugger_test.m", 241))], context("debugger_test.m", 236))], context("debugger_test.m", 222))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("mode"), [functor(atom("is"), [functor(atom("unify"), [functor(atom("in"), [], context("debugger_test.m", 198)), functor(atom("in"), [], context("debugger_test.m", 198)), functor(atom("in"), [], context("debugger_test.m", 198)), functor(atom("out"), [], context("debugger_test.m", 198))], context("debugger_test.m", 198)), functor(atom("semidet"), [], context("debugger_test.m", 198))], context("debugger_test.m", 198))], context("debugger_test.m", 198))], context("debugger_test.m", 198)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("pred"), [functor(atom("unify"), [functor(atom("term"), [], context("debugger_test.m", 197)), functor(atom("term"), [], context("debugger_test.m", 197)), functor(atom("varset"), [], context("debugger_test.m", 197)), functor(atom("varset"), [], context("debugger_test.m", 197))], context("debugger_test.m", 197))], context("debugger_test.m", 197))], context("debugger_test.m", 197)), functor(atom("true"), [], context("", 0))), clause(varset(5, two(2, "Terms0", two(1, "NewVarSet", empty, empty), four(3, "Terms", 4, "VarSet0", 5, "VarSet", empty, empty, empty, empty)), empty), functor(atom("rename_apart"), [variable(1), variable(2), variable(3), variable(4), variable(5)], context("debugger_test.m", 187)), functor(atom("varset__merge"), [variable(4), variable(1), variable(2), variable(5), variable(3)], context("debugger_test.m", 188))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("mode"), [functor(atom("is"), [functor(atom("rename_apart"), [functor(atom("in"), [], context("debugger_test.m", 185)), functor(atom("in"), [], context("debugger_test.m", 185)), functor(atom("out"), [], context("debugger_test.m", 185)), functor(atom("in"), [], context("debugger_test.m", 185)), functor(atom("out"), [], context("debugger_test.m", 185))], context("debugger_test.m", 185)), functor(atom("det"), [], context("debugger_test.m", 185))], context("debugger_test.m", 185))], context("debugger_test.m", 185))], context("debugger_test.m", 185)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("pred"), [functor(atom("rename_apart"), [functor(atom("varset"), [], context("debugger_test.m", 184)), functor(atom("list"), [functor(atom("term"), [], context("debugger_test.m", 184))], context("debugger_test.m", 184)), functor(atom("list"), [functor(atom("term"), [], context("debugger_test.m", 184))], context("debugger_test.m", 184)), functor(atom("varset"), [], context("debugger_test.m", 184)), functor(atom("varset"), [], context("debugger_test.m", 184))], context("debugger_test.m", 184))], context("debugger_test.m", 184))], context("debugger_test.m", 184)), functor(atom("true"), [], context("", 0))), clause(varset(7, three(2, "Goal", 4, "Head0", two(1, "Database", empty, empty), two(3, "ClauseVarSet", empty, empty), four(5, "Body0", 6, "Head", 7, "Body", empty, empty, empty, empty)), empty), functor(atom("-->"), [functor(atom("solve"), [variable(1), variable(2)], context("debugger_test.m", 176)), functor(atom(","), [functor(atom("{}"), [functor(atom("database_lookup_clause"), [variable(1), variable(2), variable(3), variable(4), variable(5)], context("debugger_test.m", 177))], context("debugger_test.m", 177)), functor(atom(","), [functor(atom("rename_apart"), [variable(3), functor(atom("."), [variable(4), functor(atom("."), [variable(5), functor(atom("[]"), [], context("debugger_test.m", 178))], context("debugger_test.m", 178))], context("debugger_test.m", 178)), functor(atom("."), [variable(6), functor(atom("."), [variable(7), functor(atom("[]"), [], context("debugger_test.m", 178))], context("debugger_test.m", 178))], context("debugger_test.m", 178))], context("debugger_test.m", 178)), functor(atom(","), [functor(atom("unify"), [variable(2), variable(6)], context("debugger_test.m", 179)), functor(atom("solve"), [variable(1), variable(7)], context("debugger_test.m", 180))], context("debugger_test.m", 179))], context("debugger_test.m", 178))], context("debugger_test.m", 177))], context("debugger_test.m", 176)), functor(atom("true"), [], context("", 0))), clause(varset(4, four(1, "_Database", 2, "A", 3, "B", empty, empty, empty, empty), empty), functor(atom("-->"), [functor(atom("solve"), [variable(1), functor(atom("term__functor"), [functor(atom("term__atom"), [functor(string("="), [], context("debugger_test.m", 173))], context("debugger_test.m", 173)), functor(atom("."), [variable(2), functor(atom("."), [variable(3), functor(atom("[]"), [], context("debugger_test.m", 173))], context("debugger_test.m", 173))], context("debugger_test.m", 173)), variable(4)], context("debugger_test.m", 173))], context("debugger_test.m", 173)), functor(atom("unify"), [variable(2), variable(3)], context("debugger_test.m", 174))], context("debugger_test.m", 173)), functor(atom("true"), [], context("", 0))), clause(varset(4, four(1, "Database", 2, "A", 3, "B", empty, empty, empty, empty), empty), functor(atom("-->"), [functor(atom("solve"), [variable(1), functor(atom("term__functor"), [functor(atom("term__atom"), [functor(string(";"), [], context("debugger_test.m", 168))], context("debugger_test.m", 168)), functor(atom("."), [variable(2), functor(atom("."), [variable(3), functor(atom("[]"), [], context("debugger_test.m", 168))], context("debugger_test.m", 168))], context("debugger_test.m", 168)), variable(4)], context("debugger_test.m", 168))], context("debugger_test.m", 168)), functor(atom(";"), [functor(atom("solve"), [variable(1), variable(2)], context("debugger_test.m", 169)), functor(atom("solve"), [variable(1), variable(3)], context("debugger_test.m", 171))], context("debugger_test.m", 170))], context("debugger_test.m", 168)), functor(atom("true"), [], context("", 0))), clause(varset(4, four(1, "Database", 2, "A", 3, "B", empty, empty, empty, empty), empty), functor(atom("-->"), [functor(atom("solve"), [variable(1), functor(atom("term__functor"), [functor(atom("term__atom"), [functor(string(","), [], context("debugger_test.m", 164))], context("debugger_test.m", 164)), functor(atom("."), [variable(2), functor(atom("."), [variable(3), functor(atom("[]"), [], context("debugger_test.m", 164))], context("debugger_test.m", 164))], context("debugger_test.m", 164)), variable(4)], context("debugger_test.m", 164))], context("debugger_test.m", 164)), functor(atom(","), [functor(atom("solve"), [variable(1), variable(2)], context("debugger_test.m", 165)), functor(atom("solve"), [variable(1), variable(3)], context("debugger_test.m", 166))], context("debugger_test.m", 165))], context("debugger_test.m", 164)), functor(atom("true"), [], context("", 0))), clause(varset(2, two(1, "_Database", empty, empty), empty), functor(atom("-->"), [functor(atom("solve"), [variable(1), functor(atom("term__functor"), [functor(atom("term__atom"), [functor(string("true"), [], context("debugger_test.m", 162))], context("debugger_test.m", 162)), functor(atom("[]"), [], context("debugger_test.m", 162)), variable(2)], context("debugger_test.m", 162))], context("debugger_test.m", 162)), functor(atom("[]"), [], context("debugger_test.m", 162))], context("debugger_test.m", 162)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("mode"), [functor(atom("is"), [functor(atom("solve"), [functor(atom("in"), [], context("debugger_test.m", 160)), functor(atom("in"), [], context("debugger_test.m", 160)), functor(atom("in"), [], context("debugger_test.m", 160)), functor(atom("out"), [], context("debugger_test.m", 160))], context("debugger_test.m", 160)), functor(atom("nondet"), [], context("debugger_test.m", 160))], context("debugger_test.m", 160))], context("debugger_test.m", 160))], context("debugger_test.m", 160)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("pred"), [functor(atom("solve"), [functor(atom("database"), [], context("debugger_test.m", 159)), functor(atom("term"), [], context("debugger_test.m", 159)), functor(atom("varset"), [], context("debugger_test.m", 159)), functor(atom("varset"), [], context("debugger_test.m", 159))], context("debugger_test.m", 159))], context("debugger_test.m", 159))], context("debugger_test.m", 159)), functor(atom("true"), [], context("", 0))), clause(varset(5, two(2, "Term", two(1, "VarSet", empty, empty), four(3, "Database0", 4, "Database", 5, "Database1", empty, empty, empty, empty)), empty), functor(atom("-->"), [functor(atom("consult_until_eof_2"), [functor(atom("term"), [variable(1), variable(2)], context("debugger_test.m", 142)), variable(3), variable(4)], context("debugger_test.m", 142)), functor(atom(","), [functor(atom("{}"), [functor(atom("database_assert_clause"), [variable(3), variable(1), variable(2), variable(5)], context("debugger_test.m", 143))], context("debugger_test.m", 143)), functor(atom("consult_until_eof"), [variable(5), variable(4)], context("debugger_test.m", 144))], context("debugger_test.m", 143))], context("debugger_test.m", 142)), functor(atom("true"), [], context("", 0))), clause(varset(4, two(2, "LineNumber", two(1, "ErrorMessage", empty, empty), three(3, "Database0", 4, "Database", empty, empty, empty)), empty), functor(atom("-->"), [functor(atom("consult_until_eof_2"), [functor(atom("error"), [variable(1), variable(2)], context("debugger_test.m", 134)), variable(3), variable(4)], context("debugger_test.m", 134)), functor(atom(","), [functor(atom("io__write_string"), [functor(string("Error reading term at line "), [], context("debugger_test.m", 135))], context("debugger_test.m", 135)), functor(atom(","), [functor(atom("io__write_int"), [variable(2)], context("debugger_test.m", 136)), functor(atom(","), [functor(atom("io__write_string"), [functor(string(" of standard input: "), [], context("debugger_test.m", 137))], context("debugger_test.m", 137)), functor(atom(","), [functor(atom("io__write_string"), [variable(1)], context("debugger_test.m", 138)), functor(atom(","), [functor(atom("io__write_string"), [functor(string("\n"), [], context("debugger_test.m", 139))], context("debugger_test.m", 139)), functor(atom("consult_until_eof"), [variable(3), variable(4)], context("debugger_test.m", 140))], context("debugger_test.m", 139))], context("debugger_test.m", 138))], context("debugger_test.m", 137))], context("debugger_test.m", 136))], context("debugger_test.m", 135))], context("debugger_test.m", 134)), functor(atom("true"), [], context("", 0))), clause(varset(1, two(1, "Database", empty, empty), empty), functor(atom("-->"), [functor(atom("consult_until_eof_2"), [functor(atom("eof"), [], context("debugger_test.m", 132)), variable(1), variable(1)], context("debugger_test.m", 132)), functor(atom("[]"), [], context("debugger_test.m", 132))], context("debugger_test.m", 132)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("mode"), [functor(atom("is"), [functor(atom("consult_until_eof_2"), [functor(atom("in"), [], context("debugger_test.m", 130)), functor(atom("in"), [], context("debugger_test.m", 130)), functor(atom("out"), [], context("debugger_test.m", 130)), functor(atom("di"), [], context("debugger_test.m", 130)), functor(atom("uo"), [], context("debugger_test.m", 130))], context("debugger_test.m", 130)), functor(atom("det"), [], context("debugger_test.m", 130))], context("debugger_test.m", 130))], context("debugger_test.m", 130))], context("debugger_test.m", 130)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("pred"), [functor(atom("consult_until_eof_2"), [functor(atom("read_term"), [], context("debugger_test.m", 128)), functor(atom("database"), [], context("debugger_test.m", 128)), functor(atom("database"), [], context("debugger_test.m", 128)), functor(atom("io__state"), [], context("debugger_test.m", 129)), functor(atom("io__state"), [], context("debugger_test.m", 129))], context("debugger_test.m", 128))], context("debugger_test.m", 128))], context("debugger_test.m", 128)), functor(atom("true"), [], context("", 0))), clause(varset(3, four(1, "Database0", 2, "Database", 3, "ReadTerm", empty, empty, empty, empty), empty), functor(atom("-->"), [functor(atom("consult_until_eof"), [variable(1), variable(2)], context("debugger_test.m", 124)), functor(atom(","), [functor(atom("term_io__read_term"), [variable(3)], context("debugger_test.m", 125)), functor(atom("consult_until_eof_2"), [variable(3), variable(1), variable(2)], context("debugger_test.m", 126))], context("debugger_test.m", 125))], context("debugger_test.m", 124)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("mode"), [functor(atom("is"), [functor(atom("consult_until_eof"), [functor(atom("in"), [], context("debugger_test.m", 122)), functor(atom("out"), [], context("debugger_test.m", 122)), functor(atom("di"), [], context("debugger_test.m", 122)), functor(atom("uo"), [], context("debugger_test.m", 122))], context("debugger_test.m", 122)), functor(atom("det"), [], context("debugger_test.m", 122))], context("debugger_test.m", 122))], context("debugger_test.m", 122))], context("debugger_test.m", 122)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("pred"), [functor(atom("consult_until_eof"), [functor(atom("database"), [], context("debugger_test.m", 121)), functor(atom("database"), [], context("debugger_test.m", 121)), functor(atom("io__state"), [], context("debugger_test.m", 121)), functor(atom("io__state"), [], context("debugger_test.m", 121))], context("debugger_test.m", 121))], context("debugger_test.m", 121))], context("debugger_test.m", 121)), functor(atom("true"), [], context("", 0))), clause(varset(4, two(2, "Database0", two(1, "File", empty, empty), three(3, "Database", 4, "Result", empty, empty, empty)), empty), functor(atom("-->"), [functor(atom("consult"), [variable(1), variable(2), variable(3)], context("debugger_test.m", 106)), functor(atom(","), [functor(atom("io__write_string"), [functor(string("Consulting file `"), [], context("debugger_test.m", 107))], context("debugger_test.m", 107)), functor(atom(","), [functor(atom("io__write_string"), [variable(1)], context("debugger_test.m", 108)), functor(atom(","), [functor(atom("io__write_string"), [functor(string("\'...\n"), [], context("debugger_test.m", 109))], context("debugger_test.m", 109)), functor(atom(","), [functor(atom("io__see"), [variable(1), variable(4)], context("debugger_test.m", 110)), functor(atom(";"), [functor(atom("->"), [functor(atom("{}"), [functor(atom("="), [variable(4), functor(atom("ok"), [], context("debugger_test.m", 111))], context("debugger_test.m", 111))], context("debugger_test.m", 111)), functor(atom(","), [functor(atom("consult_until_eof"), [variable(2), variable(3)], context("debugger_test.m", 112)), functor(atom("io__seen"), [], context("debugger_test.m", 113))], context("debugger_test.m", 112))], context("debugger_test.m", 111)), functor(atom(","), [functor(atom("io__write_string"), [functor(string("Error opening file `"), [], context("debugger_test.m", 115))], context("debugger_test.m", 115)), functor(atom(","), [functor(atom("io__write_string"), [variable(1)], context("debugger_test.m", 116)), functor(atom(","), [functor(atom("io__write_string"), [functor(string("\' for input.\n"), [], context("debugger_test.m", 117))], context("debugger_test.m", 117)), functor(atom("{}"), [functor(atom("="), [variable(3), variable(2)], context("debugger_test.m", 118))], context("debugger_test.m", 118))], context("debugger_test.m", 117))], context("debugger_test.m", 116))], context("debugger_test.m", 115))], context("debugger_test.m", 114))], context("debugger_test.m", 110))], context("debugger_test.m", 109))], context("debugger_test.m", 108))], context("debugger_test.m", 107))], context("debugger_test.m", 106)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("mode"), [functor(atom("is"), [functor(atom("consult"), [functor(atom("in"), [], context("debugger_test.m", 104)), functor(atom("in"), [], context("debugger_test.m", 104)), functor(atom("out"), [], context("debugger_test.m", 104)), functor(atom("di"), [], context("debugger_test.m", 104)), functor(atom("uo"), [], context("debugger_test.m", 104))], context("debugger_test.m", 104)), functor(atom("det"), [], context("debugger_test.m", 104))], context("debugger_test.m", 104))], context("debugger_test.m", 104))], context("debugger_test.m", 104)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("pred"), [functor(atom("consult"), [functor(atom("string"), [], context("debugger_test.m", 103)), functor(atom("database"), [], context("debugger_test.m", 103)), functor(atom("database"), [], context("debugger_test.m", 103)), functor(atom("io__state"), [], context("debugger_test.m", 103)), functor(atom("io__state"), [], context("debugger_test.m", 103))], context("debugger_test.m", 103))], context("debugger_test.m", 103))], context("debugger_test.m", 103)), functor(atom("true"), [], context("", 0))), clause(varset(5, two(2, "Files", two(1, "File", empty, empty), four(3, "Database0", 4, "Database", 5, "Database1", empty, empty, empty, empty)), empty), functor(atom("-->"), [functor(atom("consult_list"), [functor(atom("."), [variable(1), variable(2)], context("debugger_test.m", 99)), variable(3), variable(4)], context("debugger_test.m", 99)), functor(atom(","), [functor(atom("consult"), [variable(1), variable(3), variable(5)], context("debugger_test.m", 100)), functor(atom("consult_list"), [variable(2), variable(5), variable(4)], context("debugger_test.m", 101))], context("debugger_test.m", 100))], context("debugger_test.m", 99)), functor(atom("true"), [], context("", 0))), clause(varset(1, two(1, "Database", empty, empty), empty), functor(atom("-->"), [functor(atom("consult_list"), [functor(atom("[]"), [], context("debugger_test.m", 98)), variable(1), variable(1)], context("debugger_test.m", 98)), functor(atom("[]"), [], context("debugger_test.m", 98))], context("debugger_test.m", 98)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("mode"), [functor(atom("is"), [functor(atom("consult_list"), [functor(atom("in"), [], context("debugger_test.m", 96)), functor(atom("in"), [], context("debugger_test.m", 96)), functor(atom("out"), [], context("debugger_test.m", 96)), functor(atom("di"), [], context("debugger_test.m", 96)), functor(atom("uo"), [], context("debugger_test.m", 96))], context("debugger_test.m", 96)), functor(atom("det"), [], context("debugger_test.m", 96))], context("debugger_test.m", 96))], context("debugger_test.m", 96))], context("debugger_test.m", 96)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("pred"), [functor(atom("consult_list"), [functor(atom("list"), [functor(atom("string"), [], context("debugger_test.m", 95))], context("debugger_test.m", 95)), functor(atom("database"), [], context("debugger_test.m", 95)), functor(atom("database"), [], context("debugger_test.m", 95)), functor(atom("io__state"), [], context("debugger_test.m", 95)), functor(atom("io__state"), [], context("debugger_test.m", 95))], context("debugger_test.m", 95))], context("debugger_test.m", 95))], context("debugger_test.m", 95)), functor(atom("true"), [], context("", 0))), clause(varset(3, four(1, "VarSet", 2, "VarSets", 3, "Goal", empty, empty, empty, empty), empty), functor(atom("-->"), [functor(atom("write_solutions_2"), [functor(atom("."), [variable(1), variable(2)], context("debugger_test.m", 89)), variable(3)], context("debugger_test.m", 89)), functor(atom(","), [functor(atom("term_io__write_term_nl"), [variable(1), variable(3)], context("debugger_test.m", 90)), functor(atom("write_solutions_2"), [variable(2), variable(3)], context("debugger_test.m", 91))], context("debugger_test.m", 90))], context("debugger_test.m", 89)), functor(atom("true"), [], context("", 0))), clause(varset(1, empty, empty), functor(atom("-->"), [functor(atom("write_solutions_2"), [functor(atom("[]"), [], context("debugger_test.m", 88)), variable(1)], context("debugger_test.m", 88)), functor(atom("[]"), [], context("debugger_test.m", 88))], context("debugger_test.m", 88)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("mode"), [functor(atom("is"), [functor(atom("write_solutions_2"), [functor(atom("in"), [], context("debugger_test.m", 86)), functor(atom("in"), [], context("debugger_test.m", 86)), functor(atom("di"), [], context("debugger_test.m", 86)), functor(atom("uo"), [], context("debugger_test.m", 86))], context("debugger_test.m", 86)), functor(atom("det"), [], context("debugger_test.m", 86))], context("debugger_test.m", 86))], context("debugger_test.m", 86))], context("debugger_test.m", 86)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("pred"), [functor(atom("write_solutions_2"), [functor(atom("list"), [functor(atom("varset"), [], context("debugger_test.m", 85))], context("debugger_test.m", 85)), functor(atom("term"), [], context("debugger_test.m", 85)), functor(atom("io__state"), [], context("debugger_test.m", 85)), functor(atom("io__state"), [], context("debugger_test.m", 85))], context("debugger_test.m", 85))], context("debugger_test.m", 85))], context("debugger_test.m", 85)), functor(atom("true"), [], context("", 0))), clause(varset(2, three(1, "Solutions", 2, "Goal", empty, empty, empty), empty), functor(atom("-->"), [functor(atom("write_solutions"), [variable(1), variable(2)], context("debugger_test.m", 77)), functor(atom(";"), [functor(atom("->"), [functor(atom("{}"), [functor(atom("="), [variable(1), functor(atom("[]"), [], context("debugger_test.m", 78))], context("debugger_test.m", 78))], context("debugger_test.m", 78)), functor(atom("io__write_string"), [functor(string("No.\n"), [], context("debugger_test.m", 79))], context("debugger_test.m", 79))], context("debugger_test.m", 78)), functor(atom(","), [functor(atom("write_solutions_2"), [variable(1), variable(2)], context("debugger_test.m", 81)), functor(atom("io__write_string"), [functor(string("Yes.\n"), [], context("debugger_test.m", 82))], context("debugger_test.m", 82))], context("debugger_test.m", 81))], context("debugger_test.m", 80))], context("debugger_test.m", 77)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("mode"), [functor(atom("is"), [functor(atom("write_solutions"), [functor(atom("in"), [], context("debugger_test.m", 75)), functor(atom("in"), [], context("debugger_test.m", 75)), functor(atom("di"), [], context("debugger_test.m", 75)), functor(atom("uo"), [], context("debugger_test.m", 75))], context("debugger_test.m", 75)), functor(atom("det"), [], context("debugger_test.m", 75))], context("debugger_test.m", 75))], context("debugger_test.m", 75))], context("debugger_test.m", 75)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("pred"), [functor(atom("write_solutions"), [functor(atom("list"), [functor(atom("varset"), [], context("debugger_test.m", 74))], context("debugger_test.m", 74)), functor(atom("term"), [], context("debugger_test.m", 74)), functor(atom("io__state"), [], context("debugger_test.m", 74)), functor(atom("io__state"), [], context("debugger_test.m", 74))], context("debugger_test.m", 74))], context("debugger_test.m", 74))], context("debugger_test.m", 74)), functor(atom("true"), [], context("", 0))), clause(varset(4, two(2, "Goal", two(1, "VarSet0", empty, empty), three(3, "Database", 4, "Solutions", empty, empty, empty)), empty), functor(atom("-->"), [functor(atom("main_loop_2"), [functor(atom("term"), [variable(1), variable(2)], context("debugger_test.m", 66)), variable(3)], context("debugger_test.m", 66)), functor(atom(","), [functor(atom("{}"), [functor(atom("solutions"), [functor(atom("solve"), [variable(3), variable(2), variable(1)], context("debugger_test.m", 70)), variable(4)], context("debugger_test.m", 70))], context("debugger_test.m", 70)), functor(atom(","), [functor(atom("write_solutions"), [variable(4), variable(2)], context("debugger_test.m", 71)), functor(atom("main_loop"), [variable(3)], context("debugger_test.m", 72))], context("debugger_test.m", 71))], context("debugger_test.m", 70))], context("debugger_test.m", 66)), functor(atom("true"), [], context("", 0))), clause(varset(3, four(1, "ErrorMessage", 2, "LineNumber", 3, "Database", empty, empty, empty, empty), empty), functor(atom("-->"), [functor(atom("main_loop_2"), [functor(atom("error"), [variable(1), variable(2)], context("debugger_test.m", 59)), variable(3)], context("debugger_test.m", 59)), functor(atom(","), [functor(atom("io__write_string"), [functor(string("Error reading term at line "), [], context("debugger_test.m", 60))], context("debugger_test.m", 60)), functor(atom(","), [functor(atom("io__write_int"), [variable(2)], context("debugger_test.m", 61)), functor(atom(","), [functor(atom("io__write_string"), [functor(string(" of standard input: "), [], context("debugger_test.m", 62))], context("debugger_test.m", 62)), functor(atom(","), [functor(atom("io__write_string"), [variable(1)], context("debugger_test.m", 63)), functor(atom(","), [functor(atom("io__write_string"), [functor(string("\n"), [], context("debugger_test.m", 64))], context("debugger_test.m", 64)), functor(atom("main_loop"), [variable(3)], context("debugger_test.m", 65))], context("debugger_test.m", 64))], context("debugger_test.m", 63))], context("debugger_test.m", 62))], context("debugger_test.m", 61))], context("debugger_test.m", 60))], context("debugger_test.m", 59)), functor(atom("true"), [], context("", 0))), clause(varset(1, two(1, "_Database", empty, empty), empty), functor(atom("-->"), [functor(atom("main_loop_2"), [functor(atom("eof"), [], context("debugger_test.m", 58)), variable(1)], context("debugger_test.m", 58)), functor(atom("[]"), [], context("debugger_test.m", 58))], context("debugger_test.m", 58)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("mode"), [functor(atom("is"), [functor(atom("main_loop_2"), [functor(atom("in"), [], context("debugger_test.m", 56)), functor(atom("in"), [], context("debugger_test.m", 56)), functor(atom("di"), [], context("debugger_test.m", 56)), functor(atom("uo"), [], context("debugger_test.m", 56))], context("debugger_test.m", 56)), functor(atom("det"), [], context("debugger_test.m", 56))], context("debugger_test.m", 56))], context("debugger_test.m", 56))], context("debugger_test.m", 56)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("pred"), [functor(atom("main_loop_2"), [functor(atom("read_term"), [], context("debugger_test.m", 55)), functor(atom("database"), [], context("debugger_test.m", 55)), functor(atom("io__state"), [], context("debugger_test.m", 55)), functor(atom("io__state"), [], context("debugger_test.m", 55))], context("debugger_test.m", 55))], context("debugger_test.m", 55))], context("debugger_test.m", 55)), functor(atom("true"), [], context("", 0))), clause(varset(2, three(1, "Database", 2, "ReadTerm", empty, empty, empty), empty), functor(atom("-->"), [functor(atom("main_loop"), [variable(1)], context("debugger_test.m", 50)), functor(atom(","), [functor(atom("io__write_string"), [functor(string("?- "), [], context("debugger_test.m", 51))], context("debugger_test.m", 51)), functor(atom(","), [functor(atom("term_io__read_term"), [variable(2)], context("debugger_test.m", 52)), functor(atom("main_loop_2"), [variable(2), variable(1)], context("debugger_test.m", 53))], context("debugger_test.m", 52))], context("debugger_test.m", 51))], context("debugger_test.m", 50)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("mode"), [functor(atom("is"), [functor(atom("main_loop"), [functor(atom("in"), [], context("debugger_test.m", 48)), functor(atom("di"), [], context("debugger_test.m", 48)), functor(atom("uo"), [], context("debugger_test.m", 48))], context("debugger_test.m", 48)), functor(atom("det"), [], context("debugger_test.m", 48))], context("debugger_test.m", 48))], context("debugger_test.m", 48))], context("debugger_test.m", 48)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("pred"), [functor(atom("main_loop"), [functor(atom("database"), [], context("debugger_test.m", 47)), functor(atom("io__state"), [], context("debugger_test.m", 47)), functor(atom("io__state"), [], context("debugger_test.m", 47))], context("debugger_test.m", 47))], context("debugger_test.m", 47))], context("debugger_test.m", 47)), functor(atom("true"), [], context("", 0))), clause(varset(4, two(2, "StdErr", two(1, "Args", empty, empty), three(3, "Database0", 4, "Database", empty, empty, empty)), empty), functor(atom("-->"), [functor(atom("main"), [], context("debugger_test.m", 34)), functor(atom(","), [functor(atom("io__write_string"), [functor(string("Pure Prolog Interpreter.\n\n"), [], context("debugger_test.m", 35))], context("debugger_test.m", 35)), functor(atom(","), [functor(atom("io__command_line_arguments"), [variable(1)], context("debugger_test.m", 36)), functor(atom(";"), [functor(atom("->"), [functor(atom("{}"), [functor(atom("="), [variable(1), functor(atom("[]"), [], context("debugger_test.m", 37))], context("debugger_test.m", 37))], context("debugger_test.m", 37)), functor(atom(","), [functor(atom("io__stderr_stream"), [variable(2)], context("debugger_test.m", 38)), functor(atom(","), [functor(atom("io__write_string"), [variable(2), functor(string("Usage: interpreter filename ...\n"), [], context("debugger_test.m", 39))], context("debugger_test.m", 39)), functor(atom("io__set_exit_status"), [functor(integer(1), [], context("debugger_test.m", 40))], context("debugger_test.m", 40))], context("debugger_test.m", 39))], context("debugger_test.m", 38))], context("debugger_test.m", 37)), functor(atom(","), [functor(atom("{}"), [functor(atom("database_init"), [variable(3)], context("debugger_test.m", 42))], context("debugger_test.m", 42)), functor(atom(","), [functor(atom("consult_list"), [variable(1), variable(3), variable(4)], context("debugger_test.m", 43)), functor(atom("main_loop"), [variable(4)], context("debugger_test.m", 44))], context("debugger_test.m", 43))], context("debugger_test.m", 42))], context("debugger_test.m", 41))], context("debugger_test.m", 36))], context("debugger_test.m", 35))], context("debugger_test.m", 34)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("import_module"), [functor(atom(","), [functor(atom("list"), [], context("debugger_test.m", 32)), functor(atom(","), [functor(atom("string"), [], context("debugger_test.m", 32)), functor(atom(","), [functor(atom("term"), [], context("debugger_test.m", 32)), functor(atom(","), [functor(atom("varset"), [], context("debugger_test.m", 32)), functor(atom(","), [functor(atom("term_io"), [], context("debugger_test.m", 32)), functor(atom(","), [functor(atom("require"), [], context("debugger_test.m", 32)), functor(atom("std_util"), [], context("debugger_test.m", 32))], context("debugger_test.m", 32))], context("debugger_test.m", 32))], context("debugger_test.m", 32))], context("debugger_test.m", 32))], context("debugger_test.m", 32))], context("debugger_test.m", 32))], context("debugger_test.m", 32))], context("debugger_test.m", 32)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("implementation"), [], context("debugger_test.m", 31))], context("debugger_test.m", 31)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("mode"), [functor(atom("is"), [functor(atom("main"), [functor(atom("di"), [], context("debugger_test.m", 27)), functor(atom("uo"), [], context("debugger_test.m", 27))], context("debugger_test.m", 27)), functor(atom("det"), [], context("debugger_test.m", 27))], context("debugger_test.m", 27))], context("debugger_test.m", 27))], context("debugger_test.m", 27)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("pred"), [functor(atom("main"), [functor(atom("io__state"), [], context("debugger_test.m", 26)), functor(atom("io__state"), [], context("debugger_test.m", 26))], context("debugger_test.m", 26))], context("debugger_test.m", 26))], context("debugger_test.m", 26)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("import_module"), [functor(atom("io"), [], context("debugger_test.m", 24))], context("debugger_test.m", 24))], context("debugger_test.m", 24)), functor(atom("true"), [], contexmtrace> t("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("interface"), [], context("debugger_test.m", 23))], context("debugger_test.m", 23)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("module"), [functor(atom("interpreter"), [], context("debugger_test.m", 22))], context("debugger_test.m", 22))], context("debugger_test.m", 22)), functor(atom("true"), [], context("", 0)))]
+          HeadVar__2           		state(<<c_pointer>>)
+?-      692:    261  3    CALL DET  debugger_test:main_loop_2/4-0 
+mtrace>      693:    261  3    SWTC DET  debugger_test:main_loop_2/4-0 s3;
+mtrace>      694:    262  4     CALL NON  debugger_test:solve/4-0 
+mtrace>      695:    262  4     DISJ NON  debugger_test:solve/4-0 d1;
+mtrace> cannot print from this port
+mtrace>      696:    262  4     DISJ NON  debugger_test:solve/4-0 d2;
+mtrace>      697:    262  4     DISJ NON  debugger_test:solve/4-0 d3;
+mtrace>      698:    262  4     DISJ NON  debugger_test:solve/4-0 d4;
+mtrace>      699:    263  5      CALL SEMI debugger_test:unify/4-0 
+mtrace>      700:    263  5      SWTC SEMI debugger_test:unify/4-0 s2;
      701:    263  5      SWTC SEMI debugger_test:unify/4-0 s2;c2;s1;
      702:    263  5      ELSE SEMI debugger_test:unify/4-0 s2;c2;s1;c2;e;
      703:    264  6       CALL SEMI debugger_test:occurs_list/3-0 
      704:    264  6       FAIL SEMI debugger_test:occurs_list/3-0 
      705:    263  5      EXIT SEMI debugger_test:unify/4-0 
-trace command [a|c|d|j|n|s]      706:    262  4     EXIT NON  debugger_test:solve/4-0 
-trace command [a|c|d|j|n|s]      707:    262  4     DISJ NON  debugger_test:solve/4-0 d5;
-trace command [a|c|d|j|n|s]      708:    265  5      CALL NON  debugger_test:database_lookup_clause/5-0 
-trace command [a|c|d|j|n|s]      709:    265  5      EXIT NON  debugger_test:database_lookup_clause/5-0 
-trace command [a|c|d|j|n|s]      710:    266  5      CALL DET  debugger_test:rename_apart/5-0 
-trace command [a|c|d|j|n|s]      711:    266  5      EXIT DET  debugger_test:rename_apart/5-0 
-trace command [a|c|d|j|n|s]      712:    267  5      CALL SEMI debugger_test:unify/4-0 
-trace command [a|c|d|j|n|s]      713:    267  5      SWTC SEMI debugger_test:unify/4-0 s1;
+mtrace>      706:    262  4     EXIT NON  debugger_test:solve/4-0 
+mtrace>      707:    262  4     DISJ NON  debugger_test:solve/4-0 d5;
+mtrace>      708:    265  5      CALL NON  debugger_test:database_lookup_clause/5-0 
+mtrace>      709:    265  5      EXIT NON  debugger_test:database_lookup_clause/5-0 
+mtrace>      710:    266  5      CALL DET  debugger_test:rename_apart/5-0 
+mtrace>      711:    266  5      EXIT DET  debugger_test:rename_apart/5-0 
+mtrace>      712:    267  5      CALL SEMI debugger_test:unify/4-0 
+mtrace>      713:    267  5      SWTC SEMI debugger_test:unify/4-0 s1;
      714:    267  5      SWTC SEMI debugger_test:unify/4-0 s1;c2;s1;
      715:    267  5      FAIL SEMI debugger_test:unify/4-0 
-trace command [a|c|d|j|n|s]      716:    265  5      EXIT NON  debugger_test:database_lookup_clause/5-0 
-trace command [a|c|d|j|n|s]      717:    268  5      CALL DET  debugger_test:rename_apart/5-0 
-trace command [a|c|d|j|n|s]      718:    268  5      EXIT DET  debugger_test:rename_apart/5-0 
-trace command [a|c|d|j|n|s]      719:    269  5      CALL SEMI debugger_test:unify/4-0 
-trace command [a|c|d|j|n|s]      720:    269  5      SWTC SEMI debugger_test:unify/4-0 s1;
-trace command [a|c|d|j|n|s]      721:    269  5      SWTC SEMI debugger_test:unify/4-0 s1;c2;s1;
-trace command [a|c|d|j|n|s]      722:    269  5      FAIL SEMI debugger_test:unify/4-0 
-trace command [a|c|d|j|n|s]      723:    265  5      EXIT NON  debugger_test:database_lookup_clause/5-0 
-trace command [a|c|d|j|n|s]      724:    270  5      CALL DET  debugger_test:rename_apart/5-0 
-trace command [a|c|d|j|n|s]      725:    270  5      EXIT DET  debugger_test:rename_apart/5-0 
-trace command [a|c|d|j|n|s]      726:    271  5      CALL SEMI debugger_test:unify/4-0 
-trace command [a|c|d|j|n|s]      727:    271  5      SWTC SEMI debugger_test:unify/4-0 s1;
-trace command [a|c|d|j|n|s]      728:    271  5      SWTC SEMI debugger_test:unify/4-0 s1;c2;s1;
-trace command [a|c|d|j|n|s]      729:    271  5      FAIL SEMI debugger_test:unify/4-0 
-trace command [a|c|d|j|n|s]      730:    265  5      EXIT NON  debugger_test:database_lookup_clause/5-0 
-trace command [a|c|d|j|n|s]      731:    272  5      CALL DET  debugger_test:rename_apart/5-0 
-trace command [a|c|d|j|n|s]      732:    272  5      EXIT DET  debugger_test:rename_apart/5-0 
-trace command [a|c|d|j|n|s]      733:    273  5      CALL SEMI debugger_test:unify/4-0 
-trace command [a|c|d|j|n|s]      734:    273  5      SWTC SEMI debugger_test:unify/4-0 s1;
-trace command [a|c|d|j|n|s]      735:    273  5      SWTC SEMI debugger_test:unify/4-0 s1;c2;s1;
-trace command [a|c|d|j|n|s]      736:    273  5      FAIL SEMI debugger_test:unify/4-0 
-trace command [a|c|d|j|n|s]      737:    265  5      EXIT NON  debugger_test:database_lookup_clause/5-0 
-trace command [a|c|d|j|n|s]      738:    274  5      CALL DET  debugger_test:rename_apart/5-0 
-trace command [a|c|d|j|n|s]      739:    274  5      EXIT DET  debugger_test:rename_apart/5-0 
+mtrace>      716:    265  5      EXIT NON  debugger_test:database_lookup_clause/5-0 
+mtrace>      717:    268  5      CALL DET  debugger_test:rename_apart/5-0 
+mtrace>      718:    268  5      EXIT DET  debugger_test:rename_apart/5-0 
+mtrace>      719:    269  5      CALL SEMI debugger_test:unify/4-0 
+mtrace>      720:    269  5      SWTC SEMI debugger_test:unify/4-0 s1;
+mtrace>      721:    269  5      SWTC SEMI debugger_test:unify/4-0 s1;c2;s1;
+mtrace>      722:    269  5      FAIL SEMI debugger_test:unify/4-0 
+mtrace>      723:    265  5      EXIT NON  debugger_test:database_lookup_clause/5-0 
+mtrace>      724:    270  5      CALL DET  debugger_test:rename_apart/5-0 
+mtrace>      725:    270  5      EXIT DET  debugger_test:rename_apart/5-0 
+mtrace>      726:    271  5      CALL SEMI debugger_test:unify/4-0 
+mtrace>      727:    271  5      SWTC SEMI debugger_test:unify/4-0 s1;
+mtrace>      728:    271  5      SWTC SEMI debugger_test:unify/4-0 s1;c2;s1;
+mtrace>      729:    271  5      FAIL SEMI debugger_test:unify/4-0 
+mtrace>      730:    265  5      EXIT NON  debugger_test:database_lookup_clause/5-0 
+mtrace>      731:    272  5      CALL DET  debugger_test:rename_apart/5-0 
+mtrace>      732:    272  5      EXIT DET  debugger_test:rename_apart/5-0 
+mtrace>      733:    273  5      CALL SEMI debugger_test:unify/4-0 
+mtrace>      734:    273  5      SWTC SEMI debugger_test:unify/4-0 s1;
+mtrace>      735:    273  5      SWTC SEMI debugger_test:unify/4-0 s1;c2;s1;
+mtrace>      736:    273  5      FAIL SEMI debugger_test:unify/4-0 
+mtrace>      737:    265  5      EXIT NON  debugger_test:database_lookup_clause/5-0 
+mtrace>      738:    274  5      CALL DET  debugger_test:rename_apart/5-0 
+mtrace>      739:    274  5      EXIT DET  debugger_test:rename_apart/5-0 
      740:    275  5      CALL SEMI debugger_test:unify/4-0 
      741:    275  5      SWTC SEMI debugger_test:unify/4-0 s1;
      742:    275  5      SWTC SEMI debugger_test:unify/4-0 s1;c2;s1;
Index: tests/misc_tests/debugger_test.inp
===================================================================
RCS file: /home/mercury1/repository/tests/misc_tests/debugger_test.inp,v
retrieving revision 1.1
diff -u -u -r1.1 debugger_test.inp
--- debugger_test.inp	1998/01/25 08:44:34	1.1
+++ debugger_test.inp	1998/02/02 06:23:38
@@ -12,6 +12,7 @@
 
 
 
+p
 
 
 
@@ -19,6 +20,7 @@
 
 
 
+p
 s
 
 
@@ -30,10 +32,12 @@
 j
 
 
+p
 
 F = 1.
 
 
+p
 
 
 
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.25
diff -u -u -r1.25 mkinit.c
--- mkinit.c	1997/12/03 07:28:15	1.25
+++ mkinit.c	1998/02/02 04:44:41
@@ -78,6 +78,7 @@
 static const char mercury_funcs[] =
 	"\n"
 	"Declare_entry(%s);\n"
+	"Declare_entry(mercury__io__print_3_0);\n"
 	"\n"
 	"#ifdef CONSERVATIVE_GC\n"
 	"extern char *GC_stackbottom;\n"
@@ -131,6 +132,7 @@
 	"#endif\n"
 	"	MR_library_initializer = ML_io_init_state;\n"
 	"	MR_library_finalizer = ML_io_finalize_state;\n"
+	"	MR_library_trace_browser = ENTRY(mercury__io__print_3_0);\n"
 	"#if defined(USE_GCC_NONLOCAL_GOTOS) && !defined(USE_ASM_LABELS)\n"
 	"	do_init_modules();\n"
 	"#endif\n"



More information about the developers mailing list