for review: stack layouts for execution tracing

Tyson Dowd trd at cs.mu.OZ.AU
Thu Jan 15 16:00:40 AEDT 1998


Hi,

Can someone review this change? (Zoltan perhaps).

The code to handle the locations of typeinfo variables is still
not complete, but this code is still a useful start to others
working on execution tracing without it.

===================================================================

Estimated hours taken: 20

Reorganize options for accurate GC, stack tracing and execution tracing.
Add live value information (at entry and exit) for execution tracing.

compiler/call_gen.m:
compiler/handle_options.m:
compiler/live_vars.m:
compiler/liveness.m:
compiler/mercury_compile.m:
compiler/options.m:
compiler/unused_args.m:
	Use new options. 
	Handle new option dependencies.

compiler/code_gen.m:
	Use new options.
	Generate live value information for entry and exit points
	if we are doing execution tracing.
	Add typeinfos to livevals(...) instruction so that value
	numbering doesn't move them.

compiler/continuation_info.m:
	Add support for collecting information on live values at entry 
	and exit.
	Change the data structures to accomodate the new data collection
	needed.

compiler/stack_layout.m:
	Output tracing liveness information if needed.
	Use new options.


Index: compiler/call_gen.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/call_gen.m,v
retrieving revision 1.116
diff -u -r1.116 call_gen.m
--- call_gen.m	1998/01/13 09:57:14	1.116
+++ call_gen.m	1998/01/14 05:41:59
@@ -79,7 +79,7 @@
 
 :- import_module hlds_module, hlds_goal, hlds_data, prog_data, code_util.
 :- import_module arg_info, type_util, mode_util, unify_proc, instmap.
-:- import_module trace, globals.
+:- import_module trace, globals, options.
 :- import_module bool, int, list, assoc_list, tree, set, map.
 :- import_module std_util, require.
 
@@ -460,9 +460,10 @@
 	{ set__list_to_set(Variables0, Vars0) },
 	{ set__difference(Vars0, Args, Vars1) },
 	code_info__get_globals(Globals),
-	{ globals__get_gc_method(Globals, GC_Method) },
+	{ globals__lookup_bool_option(Globals, alternate_liveness, 
+		AlternateLiveness) },
 	( 
-		{ GC_Method = accurate }
+		{ AlternateLiveness = yes }
 	->
 		code_info__get_proc_info(ProcInfo),
 		{ proc_info_get_typeinfo_vars_setwise(ProcInfo, Vars1, 
Index: compiler/code_gen.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/code_gen.m,v
retrieving revision 1.44
diff -u -r1.44 code_gen.m
--- code_gen.m	1998/01/13 10:11:10	1.44
+++ code_gen.m	1998/01/15 04:27:00
@@ -198,8 +198,9 @@
 		MaybeFollowVars = no,
 		map__init(FollowVars)
 	),
-	globals__get_gc_method(Globals, GC_Method),
-	( GC_Method = accurate ->
+	globals__lookup_bool_option(Globals, basic_stack_layout,
+		BasicStackLayout),
+	( BasicStackLayout = yes ->
 		SaveSuccip = yes
 	;
 		SaveSuccip = no
@@ -235,7 +236,7 @@
 	;
 		Instructions = Instructions0
 	),
-	( GC_Method = accurate ->
+	( BasicStackLayout = yes ->
 		code_util__make_proc_label(ModuleInfo, PredId, ProcId,
 			ProcLabel),
 		continuation_info__add_proc_layout_info(proc(PredId, ProcId),
@@ -403,6 +404,33 @@
 	;
 		{ TraceCode = empty }
 	),
+
+		% Generate live value information and put
+		% it into the continuation info if we are doing
+		% execution tracing.
+	code_info__get_globals(Globals),
+	(
+		{ globals__lookup_bool_option(Globals, trace_stack_layout,
+			yes) }
+	->
+		code_info__get_arginfo(ArgModes),
+		code_info__get_headvars(HeadVars),
+		{ assoc_list__from_corresponding_lists(HeadVars, ArgModes,
+			Args) },
+		{ code_gen__select_args_with_mode(Args, top_in, InVars,
+			InLvals) },
+
+		code_gen__generate_lvaltypes(InVars, InLvals, LvalTypes,
+			TypeInfos),
+		
+		code_info__get_continuation_info(ContInfo0),
+		{ continuation_info__add_proc_entry_info(proc(PredId, ProcId),
+			LvalTypes, TypeInfos, ContInfo0, ContInfo) },
+		code_info__set_continuation_info(ContInfo)
+	;
+		[]
+	),
+
 	{ predicate_module(ModuleInfo, PredId, ModuleName) },
 	{ predicate_name(ModuleInfo, PredId, PredName) },
 	{ predicate_arity(ModuleInfo, PredId, Arity) },
@@ -561,7 +589,6 @@
 			]) }
 		),
 		{ RestoreDeallocCode = tree(RestoreSuccipCode, DeallocCode ) },
-		{ code_gen__output_args(Args, LiveArgs) },
 		code_info__get_maybe_trace_info(MaybeTraceInfo),
 		( { MaybeTraceInfo = yes(TraceInfo) } ->
 			trace__generate_event_code(exit, TraceInfo,
@@ -576,6 +603,35 @@
 			{ SuccessTraceCode = empty },
 			{ FailureTraceCode = empty }
 		),
+			% Generate live value information and put
+			% it into the continuation info if we are doing
+			% execution tracing.
+		{ code_gen__select_args_with_mode(Args, top_out, OutVars,
+			OutLvals) },
+		code_info__get_globals(Globals),
+		(
+			{ globals__lookup_bool_option(Globals,
+				trace_stack_layout, yes) }
+		->
+			code_gen__generate_lvaltypes(OutVars, OutLvals,
+				LvalTypes, 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) },
+			code_info__set_continuation_info(ContInfo),
+
+				% Make sure typeinfos are in livevals(...)
+				% so that value numbering doesn't mess
+				% with them.
+			{ assoc_list__values(TypeInfos, ExtraLvals) },
+			{ list__append(ExtraLvals, OutLvals, LiveArgLvals) }
+		;
+			{ LiveArgLvals = OutLvals }
+		),
+		{ set__list_to_set(LiveArgLvals, LiveArgs) },
 		(
 			{ CodeModel = model_det },
 			{ SuccessCode = node([
@@ -638,6 +694,36 @@
 
 %---------------------------------------------------------------------------%
 
+	% Generate the list of lval - live_value_type pairs and the
+	% typeinfo variable - lval pairs for any type variables in
+	% the types of the input 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) -->
+	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) },
+
+	% 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) }.
+
+%---------------------------------------------------------------------------%
+
 % Generate a goal. This predicate arranges for the necessary updates of
 % the generic data structures before and after the actual code generation,
 % which is delegated to context-specific predicates.
@@ -1072,18 +1158,29 @@
 
 %---------------------------------------------------------------------------%
 
-code_gen__output_args([], LiveVals) :-
-	set__init(LiveVals).
-code_gen__output_args([_V - arg_info(Loc, Mode) | Args], Vs) :-
-	code_gen__output_args(Args, Vs0),
+code_gen__output_args(Args, Vs) :-
+	code_gen__select_args_with_mode(Args, top_out, _, Lvals),
+	set__list_to_set(Lvals, Vs).
+
+:- pred code_gen__select_args_with_mode(assoc_list(var, arg_info), 
+	arg_mode, list(var), list(lval)).
+:- mode code_gen__select_args_with_mode(in, in, out, out) is det.
+
+code_gen__select_args_with_mode([], _, [], []).
+code_gen__select_args_with_mode([Var - ArgInfo | Args], Mode, Vs, Ls) :-
+	code_gen__select_args_with_mode(Args, Mode, Vs0, Ls0),
+	ArgInfo = arg_info(Loc, Mode1),
 	(
-		Mode = top_out
+		Mode = Mode1
 	->
 		code_util__arg_loc_to_register(Loc, Reg),
-		set__insert(Vs0, Reg, Vs)
+		Vs = [Var | Vs0],
+		Ls = [Reg | Ls0]
 	;
-		Vs = Vs0
+		Vs = Vs0,
+		Ls = Ls0
 	).
+
 
 %---------------------------------------------------------------------------%
 
Index: compiler/continuation_info.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/continuation_info.m,v
retrieving revision 1.6
diff -u -r1.6 continuation_info.m
--- continuation_info.m	1998/01/13 09:57:58	1.6
+++ continuation_info.m	1998/01/14 06:33:03
@@ -11,17 +11,28 @@
 % to hold the information we need to output stack_layout tables for
 % accurate garbage collection.
 %
-% Information is collected in two passes. 
-% 	1. After the code for a procedure has been generated, a
-% 	   proc_layout_info is added to the continuation info (using
-% 	   continuation_info__add_proc_layout_info). 
-% 	2. After code has been optimized, a pass is made over the
-% 	   final LLDS instructions. Information about internal labels,
-% 	   is collected. The liveness information in call instructions
-% 	   is stored with the corresponding continuation label.
+% Information is collected in several passes. 
+%	- If trace_stack_layouts are needed, during the generation of the 
+%	  procedure's prolog code (in code_gen.m) we add the information
+%	  about live values at entry.
+%	- If execution tracing is needed, 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 a pass is made over the final LLDS
+% 	  instructions. Information about internal labels, is collected.
+% 	  The liveness information in call instructions is stored with the
+% 	  corresponding continuation label.
 %
 % stack_layout.m converts the information collected in this module into
 % stack_layout tables.
+%		
+% The data structures in this module could do with a re-design when it
+% becomes more stable.
 
 %-----------------------------------------------------------------------------%
 
@@ -47,12 +58,22 @@
 :- type proc_layout_info
 	--->
 		proc_layout_info(
+			maybe(proc_layout_general_info),
+			map(label, internal_layout_info),
+					% info for each internal label
+			maybe(continuation_label_info),  % entry
+			maybe(continuation_label_info)	 % exit
+					% live data information about
+					% entry and exit points
+		).
+
+:- type proc_layout_general_info
+	--->
+		proc_layout_general_info(
 			proc_label,	% the proc label
 			int,		% number of stack slots
 			code_model,	% which stack is used
-			maybe(int),	% location of succip on stack
-			map(label, internal_layout_info)
-					% info for each internal label
+			maybe(int)	% location of succip on stack
 		).
 
 	%
@@ -104,6 +125,15 @@
 :- 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),
+		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),
+		continuation_info, continuation_info).
+:- mode continuation_info__add_proc_exit_info(in, in, in, in, out) is det.
 
 :- pred continuation_info__process_llds(list(c_procedure),
 		continuation_info, continuation_info) is det.
@@ -164,6 +194,28 @@
 	map__init(Internals),
 	ContInfo = continuation_info(LabelMap, Internals).
 
+continuation_info__add_proc_entry_info(PredProcId, TypeLvals, TypeInfos) -->
+	continuation_info__get_proc_layout(PredProcId, ProcLayout0),
+	{ ProcLayout0 = proc_layout_info(MaybeProcGeneral, InternalMap, _,
+		ExitInfo) },
+	{ set__list_to_set(TypeLvals, TypeLvalSet) },
+	{ set__list_to_set(TypeInfos, TypeInfoSet) },
+	{ EntryInfo = yes(continuation_label_info(TypeLvalSet, TypeInfoSet)) },
+	{ ProcLayout = proc_layout_info(MaybeProcGeneral, InternalMap, 
+		EntryInfo, ExitInfo) },
+	continuation_info__update_proc_layout(PredProcId, ProcLayout).
+
+continuation_info__add_proc_exit_info(PredProcId, TypeLvals, TypeInfos) -->
+	continuation_info__get_proc_layout(PredProcId, ProcLayout0),
+	{ ProcLayout0 = proc_layout_info(MaybeProcGeneral, InternalMap, 
+		EntryInfo, _) },
+	{ set__list_to_set(TypeLvals, TypeLvalSet) },
+	{ set__list_to_set(TypeInfos, TypeInfoSet) },
+	{ ExitInfo = yes(continuation_label_info(TypeLvalSet, TypeInfoSet)) },
+	{ ProcLayout = proc_layout_info(MaybeProcGeneral, InternalMap, 
+		EntryInfo, ExitInfo) },
+	continuation_info__update_proc_layout(PredProcId, ProcLayout).
+	
 continuation_info__process_llds([]) --> [].
 continuation_info__process_llds([Proc|Procs]) -->
 	{ Proc = c_procedure(_, _, PredProcId, Instrs) },
@@ -209,14 +261,19 @@
 	% continuation_info. 
 	%
 continuation_info__add_proc_layout_info(PredProcId, ProcLabel, StackSize,
-		CodeModel, SuccipLocation, ContInfo0, ContInfo) :-
-
-		% We don't know anything about the internals yet.
-	map__init(InternalMap),
-	ProcLayoutInfo = proc_layout_info(ProcLabel, StackSize, CodeModel,
-		SuccipLocation, InternalMap),
-	continuation_info__insert_proc_layout(PredProcId, ProcLayoutInfo,
-		ContInfo0, ContInfo).
+		CodeModel, 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)), 
+			InternalMap, EntryInfo, ExitInfo)
+	;
+		error("continuation_info__add_proc_layout_info: general information already done.")
+	},
+	continuation_info__update_proc_layout(PredProcId, ProcLayoutInfo).
 
 	%
 	% Get all the proc_layout_infos.
@@ -336,6 +393,39 @@
 	ContInfo = continuation_info(ProcLayoutMap, Internals).
 
 	%
+	% Get the proc layout if it exists, otherwise return an 
+	% empty one.
+	%
+:- pred continuation_info__get_proc_layout(pred_proc_id, proc_layout_info,
+		continuation_info, continuation_info).
+:- mode continuation_info__get_proc_layout(in, out, in, out) is det.
+
+continuation_info__get_proc_layout(PredProcId, ProcLayoutInfo,
+		ContInfo, ContInfo) :-
+	ContInfo = continuation_info(ProcLayoutMap, _Internals),
+	( 
+		map__search(ProcLayoutMap, PredProcId, ProcLayoutInfo0)
+	->
+		ProcLayoutInfo = ProcLayoutInfo0
+	;
+		map__init(InternalMap),
+		ProcLayoutInfo = proc_layout_info(no, InternalMap, no, no)
+	).
+
+	%
+	% Update a proc layout.
+	%
+:- pred continuation_info__update_proc_layout(pred_proc_id, proc_layout_info,
+		continuation_info, continuation_info).
+:- mode continuation_info__update_proc_layout(in, in, in, out) is det.
+
+continuation_info__update_proc_layout(PredProcId, ProcLayoutInfo,
+		ContInfo0, ContInfo) :-
+	ContInfo0 = continuation_info(ProcLayoutMap0, Internals),
+	map__set(ProcLayoutMap0, PredProcId, ProcLayoutInfo, ProcLayoutMap),
+	ContInfo = continuation_info(ProcLayoutMap, Internals).
+
+	%
 	% Add the given internal_info to the given procedure in
 	% the continuation_info.
 	%
@@ -351,10 +441,10 @@
 		ContInfo0, ContInfo) :-
 	ContInfo0 = continuation_info(ProcLayoutMap0, Internals),
 	map__lookup(ProcLayoutMap0, PredProcId, ProcLayoutInfo0),
-	ProcLayoutInfo0 = proc_layout_info(ProcLabel, StackSize, CodeModel,
-		SuccipLocation, _),
-	ProcLayoutInfo = proc_layout_info(ProcLabel, StackSize, CodeModel,
-		SuccipLocation, InternalLayout),
+	ProcLayoutInfo0 = proc_layout_info(MaybeProcGeneral, _, EntryInfo,
+		ExitInfo),
+	ProcLayoutInfo = proc_layout_info(MaybeProcGeneral, InternalLayout,
+		EntryInfo, ExitInfo),
 	map__set(ProcLayoutMap0, PredProcId, ProcLayoutInfo, ProcLayoutMap),
 	ContInfo = continuation_info(ProcLayoutMap, Internals).
 
Index: compiler/handle_options.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/handle_options.m,v
retrieving revision 1.39
diff -u -r1.39 handle_options.m
--- handle_options.m	1998/01/07 05:39:51	1.39
+++ handle_options.m	1998/01/08 13:00:05
@@ -267,8 +267,11 @@
 		[]
 	),
 
-	% --generate-trace requires disabling optimizations
-	% that would change the trace being generated
+	% --generate-trace requires 
+	% 	- disabling optimizations that would change 
+	% 	  the trace being generated
+	% 	- enabling stack layouts
+	% 	- enabling alternate liveness
 	globals__io_lookup_bool_option(generate_trace, Trace),
 	( { Trace = yes } ->
 		globals__io_set_option(inline_simple, bool(no)),
@@ -278,17 +281,27 @@
 		globals__io_set_option(optimize_higher_order, bool(no)),
 		globals__io_set_option(optimize_duplicate_calls, bool(no)),
 		globals__io_set_option(optimize_constructor_last_call,
-			bool(no))
+			bool(no)),
+		globals__io_set_option(trace_stack_layout, bool(yes)),
+		globals__io_set_option(alternate_liveness, bool(yes))
 	;
 		[]
 	),
 
-	% --gc accurate requires stack layouts.
+	% --stack-trace requires basic stack layouts
+	option_implies(stack_trace, basic_stack_layout, bool(yes)),
+
+	% --gc accurate requires stack layouts and alternate liveness.
 	( { GC_Method = accurate } ->
-		globals__io_set_option(stack_layout, bool(yes)) 
+		globals__io_set_option(agc_stack_layout, bool(yes)),
+		globals__io_set_option(alternate_liveness, bool(yes)) 
 	;
 		[]
 	),
+
+	% `agc' and `trace' stack layouts need `basic' stack layouts
+	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/staff/zs/imp/mercury/compiler/live_vars.m,v
retrieving revision 1.70
diff -u -r1.70 live_vars.m
--- live_vars.m	1998/01/13 10:12:28	1.70
+++ live_vars.m	1998/01/14 06:35:30
@@ -35,8 +35,8 @@
 :- implementation.
 
 :- import_module llds, arg_info, prog_data, hlds_goal, hlds_data, mode_util.
-:- import_module liveness, code_aux, globals, graph_colour, instmap.
-:- import_module list, map, set, std_util, assoc_list.
+:- import_module liveness, code_aux, globals, graph_colour, instmap, options.
+:- import_module list, map, set, std_util, assoc_list, bool.
 :- import_module int, term, require.
 
 %-----------------------------------------------------------------------------%
@@ -237,9 +237,10 @@
 	set__difference(Liveness, OutVars, InputLiveness),
 	set__union(InputLiveness, ResumeVars0, StackVars0),
 
-	% Might need to add more live variables with accurate GC.
+	% Might need to add more live variables with alternate liveness
+	% calculation.
 
-	maybe_add_accurate_gc_typeinfos(ModuleInfo, ProcInfo,
+	maybe_add_alternate_liveness_typeinfos(ModuleInfo, ProcInfo,
 		OutVars, StackVars0, StackVars),
 
 	set__insert(LiveSets0, StackVars, LiveSets),
@@ -275,9 +276,10 @@
 	set__difference(Liveness, OutVars, InputLiveness),
 	set__union(InputLiveness, ResumeVars0, StackVars0),
 
-	% Might need to add more live variables with accurate GC.
+	% Might need to add more live variables with alternate liveness
+	% calculation.
 
-	maybe_add_accurate_gc_typeinfos(ModuleInfo, ProcInfo,
+	maybe_add_alternate_liveness_typeinfos(ModuleInfo, ProcInfo,
 		OutVars, StackVars0, StackVars),
 
 	set__insert(LiveSets0, StackVars, LiveSets),
@@ -312,9 +314,10 @@
 		set__difference(Liveness, OutVars, InputLiveness),
 		set__union(InputLiveness, ResumeVars0, StackVars0),
 
-		% Might need to add more live variables with accurate GC.
+		% Might need to add more live variables with alternate
+		% liveness calculation.
 
-		maybe_add_accurate_gc_typeinfos(ModuleInfo,
+		maybe_add_alternate_liveness_typeinfos(ModuleInfo,
 			ProcInfo, OutVars, StackVars0, StackVars),
 
 		set__insert(LiveSets0, StackVars, LiveSets),
@@ -372,9 +375,10 @@
 		set__difference(Liveness, OutVars, InputLiveness),
 		set__union(InputLiveness, ResumeVars0, StackVars0),
 
-		% Might need to add more live variables with accurate GC.
+		% Might need to add more live variables with alternate
+		% liveness calculation.
 
-		maybe_add_accurate_gc_typeinfos(ModuleInfo,
+		maybe_add_alternate_liveness_typeinfos(ModuleInfo,
 			ProcInfo, OutVars, StackVars0, StackVars),
 
 		set__insert(LiveSets0, StackVars, LiveSets),
@@ -468,9 +472,9 @@
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
 
-	% If doing accurate garbage collection, any typeinfos for
+	% If doing alternate liveness calculation, any typeinfos for
 	% output variables or live variables are also live.
-	% This is because if you want to collect, you need to
+	% This is because if you want to examine the live data, you need to
 	% know what shape the polymorphic args of the variables
 	% are, so you need the typeinfos to be present on the stack.
 
@@ -479,24 +483,25 @@
 	% saved (otherwise we would throw out typeinfos and might
 	% need one at a continuation point just after a call).
 
-	% maybe_add_accurate_gc_typeinfos takes a set of vars
+	% maybe_add_alternate_liveness_typeinfos takes a set of vars
 	% (output vars) and a set of live vars and if we
-	% are doing accurate GC, add the appropriate typeinfo variables to the
-	% set of variables. If not, return the live vars unchanged.
+	% are doing alternate liveness, adds the appropriate typeinfo
+	% variables to the set of variables. If not, it returns the live
+	% vars unchanged.
 
 	% Make sure you get the output vars first, and the live vars second,
 	% since this makes a significant difference to the output set of vars.
 
-:- pred maybe_add_accurate_gc_typeinfos(module_info, proc_info,
+:- pred maybe_add_alternate_liveness_typeinfos(module_info, proc_info,
 	set(var), set(var), set(var)).
-:- mode maybe_add_accurate_gc_typeinfos(in, in, in, in, out) is det.
+:- mode maybe_add_alternate_liveness_typeinfos(in, in, in, in, out) is det.
 
-maybe_add_accurate_gc_typeinfos(ModuleInfo, ProcInfo, OutVars,
-	LiveVars1, LiveVars) :-
+maybe_add_alternate_liveness_typeinfos(ModuleInfo, ProcInfo, OutVars,
+		LiveVars1, LiveVars) :-
 	module_info_globals(ModuleInfo, Globals),
-	globals__get_gc_method(Globals, GC_Method),
+	globals__lookup_bool_option(Globals, alternate_liveness, AlternateLive),
 	(
-		GC_Method = accurate
+		AlternateLive = yes
 	->
 		proc_info_get_typeinfo_vars_setwise(ProcInfo, LiveVars1,
 			TypeInfoVarsLive),
Index: compiler/liveness.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/liveness.m,v
retrieving revision 1.88
diff -u -r1.88 liveness.m
--- liveness.m	1998/01/13 10:12:34	1.88
+++ liveness.m	1998/01/14 05:42:29
@@ -52,15 +52,13 @@
 % code at that resume point as well as the nature of the required
 % entry labels.
 %
-% Accurate garbage collection notes:
+% Alternate liveness calculation notes:
 %
-% When using accurate gc, liveness is computed slightly differently.
-% The garbage collector needs access to the typeinfo variables of any
-% variable that could be live at a garbage collection point. In the
-% present design of the garbage collector, garbage collection takes place
-% at procedure returns.
+% When using accurate gc or execution tracing, liveness is computed
+% slightly differently.  The runtime system access to the
+% typeinfo variables of any variable that is live at a continuation.
 % 
-% Hence, the invariant needed for accurate GC is:
+% Hence, the invariant needed for alternate liveness calculation:
 % 	a variable holding a typeinfo must be live at any continuation
 % 	where any variable whose type is described (in whole or in part)
 % 	by that typeinfo is live.
@@ -85,7 +83,7 @@
 % 
 % (1) happens without any changes to the liveness computation (it is
 %     the normal condition for variables becoming dead). This more
-%     conservative than what is required for accurate GC, but is
+%     conservative than what is required for the invariant, but is
 %     required for code generation, so we should keep it ;-)
 % (2) is implemented by adding the typeinfo variables for the types of the
 %     nonlocals to the nonlocals for the purposes of computing liveness.
@@ -145,7 +143,7 @@
 :- implementation.
 
 :- import_module hlds_goal, hlds_data, llds, quantification, (inst), instmap.
-:- import_module hlds_out, mode_util, code_util, quantification.
+:- import_module hlds_out, mode_util, code_util, quantification, options.
 :- import_module prog_data, globals, passes_aux.
 :- import_module bool, list, map, set, std_util, term, assoc_list, require.
 :- import_module varset, string.
@@ -876,18 +874,20 @@
 		error("initial_liveness: list length mismatch")
 	),
 	module_info_globals(ModuleInfo, Globals),
-	globals__get_gc_method(Globals, GCmethod),
 
 		% If a variable is unused in the goal, it shouldn't be
 		% in the initial liveness. (If we allowed it to start
 		% live, it wouldn't ever become dead, because it would
 		% have to be used to be killed).
 		% So we intersect the headvars with the non-locals and
-		% their typeinfo vars.
+		% (if doing alternate liveness calculation) their
+		% typeinfo vars.
 	proc_info_goal(ProcInfo, _Goal - GoalInfo),
 	goal_info_get_nonlocals(GoalInfo, NonLocals0),
-	(
-		GCmethod = accurate
+	globals__lookup_bool_option(Globals, alternate_liveness, 
+		AlternateLiveness),
+	( 	
+		AlternateLiveness = yes
 	->
 		proc_info_get_typeinfo_vars_setwise(ProcInfo, NonLocals0,
 			TypeInfoNonLocals),
@@ -933,12 +933,13 @@
 	;
 		error("initial_deadness: list length mis-match")
 	),
-		% If doing accurate garbage collection, the corresponding
+		% If doing alternate liveness, the corresponding
 		% typeinfos need to be added to these.
 	module_info_globals(ModuleInfo, Globals),
-	globals__get_gc_method(Globals, GCmethod),
-	(
-		GCmethod = accurate
+	globals__lookup_bool_option(Globals, alternate_liveness, 
+		AlternateLiveness),
+	( 
+		AlternateLiveness = yes
 	->
 		proc_info_get_typeinfo_vars_setwise(ProcInfo, Deadness2,
 			TypeInfoVars),
@@ -1053,7 +1054,7 @@
 
 %-----------------------------------------------------------------------------%
 
-	% Get the nonlocals, and, if doing accurate GC, add the
+	% Get the nonlocals, and, if doing alternate liveness, add the
 	% typeinfo vars for the nonlocals.
 
 :- pred liveness__get_nonlocals_and_typeinfos(live_info, hlds_goal_info,
@@ -1063,10 +1064,11 @@
 		NonLocals) :-
 	live_info_get_module_info(LiveInfo, ModuleInfo),
 	module_info_globals(ModuleInfo, Globals),
-	globals__get_gc_method(Globals, GCmethod),
 	goal_info_get_nonlocals(GoalInfo, NonLocals0),
-	(
-		GCmethod = accurate
+	globals__lookup_bool_option(Globals, alternate_liveness, 
+		AlternateLiveness),
+	( 
+		AlternateLiveness = yes
 	->
 		live_info_get_proc_info(LiveInfo, ProcInfo),
 		proc_info_get_typeinfo_vars_setwise(ProcInfo, NonLocals0,
Index: compiler/mercury_compile.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/mercury_compile.m,v
retrieving revision 1.71
diff -u -r1.71 mercury_compile.m
--- mercury_compile.m	1998/01/09 07:34:10	1.71
+++ mercury_compile.m	1998/01/14 05:42:33
@@ -958,13 +958,14 @@
 	;
 		{ Proc = Proc0 }
 	),
-	{ globals__lookup_bool_option(Globals, stack_layout, StackLayout) },
-	( { StackLayout = yes } ->
+	{ globals__lookup_bool_option(Globals, basic_stack_layout,
+		BasicStackLayout) },
+	( { BasicStackLayout = yes } ->
 		{ Proc = c_procedure(_, _, PredProcId, Instructions) },
 		{ module_info_get_continuation_info(ModuleInfo5, ContInfo2) },
 		write_proc_progress_message(
-			"% Generating stack layout information for ",
-					PredId, ProcId, ModuleInfo5),
+		   "% Generating stack layout continuation information for ",
+				PredId, ProcId, ModuleInfo5),
 		{ continuation_info__process_instructions(PredProcId,
 			Instructions, ContInfo2, ContInfo3) },
 		{ module_info_set_continuation_info(ModuleInfo5, ContInfo3, 
@@ -1591,10 +1592,10 @@
 
 mercury_compile__maybe_generate_stack_layouts(ModuleInfo0, LLDS0, Verbose, 
 		Stats, ModuleInfo) -->
-	globals__io_lookup_bool_option(stack_layout, StackLayout),
+	globals__io_lookup_bool_option(agc_stack_layout, StackLayout),
 	( { StackLayout = yes } ->
 		maybe_write_string(Verbose,
-			"% Generating stack layout information..."),
+			"% Generating stack layout continuation information..."),
 		maybe_flush_output(Verbose),
 		{ module_info_get_continuation_info(ModuleInfo0, ContInfo0) },
 		{ continuation_info__process_llds(LLDS0, ContInfo0,
@@ -1619,12 +1620,17 @@
 mercury_compile__output_pass(HLDS0, LLDS0, ModuleName, CompileErrors) -->
 	globals__io_lookup_bool_option(verbose, Verbose),
 	globals__io_lookup_bool_option(statistics, Stats),
+	globals__io_lookup_bool_option(basic_stack_layout, BasicStackLayout),
 
 	{ base_type_info__generate_llds(HLDS0, BaseTypeInfos) },
 	{ base_type_layout__generate_llds(HLDS0, HLDS1, BaseTypeLayouts) },
-	{ stack_layout__generate_llds(HLDS1, HLDS, StackLayouts) },
-
-	{ list__append(StackLayouts, BaseTypeLayouts, StaticData0) },
+	{ BasicStackLayout = yes ->
+		stack_layout__generate_llds(HLDS1, HLDS, StackLayouts),
+		list__append(StackLayouts, BaseTypeLayouts, StaticData0)
+	;
+		HLDS = HLDS1,
+		StaticData0 = BaseTypeLayouts
+	},
 
 	{ llds_common(LLDS0, StaticData0, ModuleName, LLDS1, 
 		StaticData, CommonData) },
Index: compiler/options.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/options.m,v
retrieving revision 1.218
diff -u -r1.218 options.m
--- options.m	1998/01/06 23:51:01	1.218
+++ options.m	1998/01/08 07:20:47
@@ -118,6 +118,7 @@
 		;	profile_calls
 		;	profile_time
 		;	profile_memory
+		;	stack_trace
 		;	use_trail
 		;	pic_reg
 		;	debug
@@ -140,11 +141,19 @@
 		;	args
 		;	type_info
 		;	type_layout
-				% XXX stack_layout is a development only 
-				% option. It will eventually be replaced
-				% by new options handling different
-				% sorts of stack_layouts.
-		;	stack_layout
+				% Stack layout information required to do
+				% a stack trace.
+		;	basic_stack_layout
+				% Stack layout information required to do
+				% accurate GC.
+		;	agc_stack_layout
+				% Stack layout information required to do
+				% tracing.
+		;	trace_stack_layout
+				% Use alternate calculation of liveness
+				% where typeinfos are live for any live data
+				% the includes that type variable.
+		;	alternate_liveness
 		;	highlevel_c
 		;	unboxed_float
 	% Code generation options
@@ -379,6 +388,7 @@
 	profile_calls		-	bool(no),
 	profile_time		-	bool(no),
 	profile_memory		-	bool(no),
+	stack_trace		-	bool(no),
 	use_trail		-	bool(no),
 	pic_reg			-	bool(no),
 	debug			-	bool(no),
@@ -400,7 +410,10 @@
 	args			-	string("compact"),
 	type_info		-	string("default"),
 	type_layout		-	bool(yes),
-	stack_layout		-	bool(no),
+	basic_stack_layout	-	bool(no),
+	agc_stack_layout	-	bool(no),
+	trace_stack_layout	-	bool(no),
+	alternate_liveness	-	bool(no),
 	highlevel_c		-	bool(no),
 	unboxed_float		-	bool(no)
 ]).
@@ -682,6 +695,7 @@
 long_option("profile-calls",		profile_calls).
 long_option("profile-time",		profile_time).
 long_option("profile-memory",		profile_memory).
+long_option("stack-trace",		stack_trace).
 long_option("use-trail",		use_trail).
 long_option("pic-reg",			pic_reg).
 long_option("debug",			debug).
@@ -695,7 +709,10 @@
 long_option("type-info",		type_info).
 long_option("type-info-convention",	type_info).
 long_option("type-layout",		type_layout).
-long_option("stack-layout",		type_layout).
+long_option("agc-stack-layout",		agc_stack_layout).
+long_option("basic-stack-layout",	basic_stack_layout).
+long_option("trace-stack-layout",	trace_stack_layout).
+long_option("alternate-liveness",	alternate_liveness).
 long_option("highlevel-C",		highlevel_c).
 long_option("highlevel-c",		highlevel_c).
 long_option("high-level-C",		highlevel_c).
@@ -1488,11 +1505,31 @@
 	io__write_string("\t\tto them. (The C code also needs to be compiled with\n"),
 	io__write_string("\t\t`-DNO_TYPE_LAYOUT').\n"),
 	
-		% This is a developer only option at the moment.
-%	io__write_string("\t--stack-layout\n"),
+		% This is a developer only option.
+%	io__write_string("\t--basic-stack-layout\n"),
 %	io__write_string("\t(This option is not for general use.)\n"),
-%	io__write_string("\t\tGenerate stack_layout structures.\n"),
+%	io__write_string("\t\tGenerate the simple stack_layout structures required\n"),
+%	io__write_string("\t\tfor stack traces.\n"),
 
+		% This is a developer only option.
+%	io__write_string("\t--agc-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\taccurate garbage collection.\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(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"),
+%	io__write_string("\t\tthat has a type that contains that type variable is live\n"),
+%
 	io__write_string("\t--unboxed-float\n"),
 	io__write_string("\t(This option is not for general use.)\n"),
 	io__write_string("\t\tDon't box floating point numbers.\n"),
Index: compiler/stack_layout.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/stack_layout.m,v
retrieving revision 1.4
diff -u -r1.4 stack_layout.m
--- stack_layout.m	1998/01/06 07:07:31	1.4
+++ stack_layout.m	1998/01/14 03:41:17
@@ -28,6 +28,22 @@
 % 					(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:
@@ -68,7 +84,7 @@
 :- implementation.
 
 :- import_module llds, globals, options, continuation_info, llds_out.
-:- import_module base_type_layout.
+:- import_module base_type_layout, prog_data.
 :- import_module assoc_list, bool, string, int, list, map, std_util, require.
 :- import_module set.
 
@@ -76,9 +92,12 @@
 	stack_layout_info(
 		string,		% module name
 		int,		% next available cell number 
+		bool,		% generate agc layout info?
+		bool,		% generate tracing layout info?
 		list(c_module)	% generated data
 	).
 
+
 %---------------------------------------------------------------------------%
 
 	% Initialize the StackLayoutInfo, and begin processing.
@@ -89,8 +108,12 @@
 
 	module_info_name(ModuleInfo0, ModuleName),
 	module_info_get_cell_count(ModuleInfo0, CellCount),
+	module_info_globals(ModuleInfo0, Globals),
+	globals__lookup_bool_option(Globals, agc_stack_layout, AgcLayout),
+	globals__lookup_bool_option(Globals, trace_stack_layout, TraceLayout),
 
-	LayoutInfo0 = stack_layout_info(ModuleName, CellCount, []),
+	LayoutInfo0 = stack_layout_info(ModuleName, CellCount, AgcLayout,
+		TraceLayout, []),
 	list__foldl(stack_layout__construct_layouts, ProcLayoutList,
 		LayoutInfo0, LayoutInfo),
 
@@ -108,25 +131,33 @@
 
 stack_layout__construct_layouts(ProcLayoutInfo) -->
 
-	{ ProcLayoutInfo = proc_layout_info(ProcLabel, StackSlots, CodeModel, 
-		SuccipLoc, InternalMap) },
+	{ ProcLayoutInfo = proc_layout_info(MaybeGeneralInfo, InternalMap, 
+		EntryInfo, ExitInfo) },
 
-	{ map__to_assoc_list(InternalMap, Internals) },
+	( { MaybeGeneralInfo = yes(GeneralInfo) } ->
+		stack_layout__construct_proc_layout(GeneralInfo, EntryInfo,
+			ExitInfo),
+		{ GeneralInfo = proc_layout_general_info(ProcLabel, _, _, _) },
+		{ map__to_assoc_list(InternalMap, Internals) },
+		list__foldl(stack_layout__construct_internal_layout(ProcLabel),
+			Internals)
+	;
+		{ error("stack_layout__construct_layouts: uninitialized proc layout") }
+	).
 
-	stack_layout__construct_proc_layout(ProcLabel, StackSlots, 
-		CodeModel, SuccipLoc),
-	list__foldl(stack_layout__construct_internal_layout(ProcLabel),
-		Internals).
 
 %---------------------------------------------------------------------------%
 
 	% Construct the layout describing a single procedure.
 
-:- pred stack_layout__construct_proc_layout(proc_label, int, code_model, 
-		maybe(int), stack_layout_info, stack_layout_info).
-:- mode stack_layout__construct_proc_layout(in, in, in, in, in, out) is det.
-stack_layout__construct_proc_layout(ProcLabel, StackSlots, CodeModel, 
-		SuccipLoc) -->
+:- 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.
+stack_layout__construct_proc_layout(GeneralInfo, MaybeEntryInfo,
+		MaybeExitInfo) -->
+	{ GeneralInfo = proc_layout_general_info(ProcLabel, StackSlots, 
+		CodeModel, SuccipLoc) },
 	{
 		SuccipLoc = yes(Location0)
 	->
@@ -154,10 +185,22 @@
 	{ CodeAddrRval = const(code_addr_const(label(Label))) },
 
 	stack_layout__represent_code_model(CodeModel, CodeModelRval),
-	{ MaybeRvals = [yes(CodeAddrRval), yes(StackSlotsRval), 
+	{ MaybeRvals0 = [yes(CodeAddrRval), yes(StackSlotsRval), 
 		yes(CodeModelRval), yes(SuccipRval)] },
 	stack_layout__get_module_name(ModuleName),
 
+	stack_layout__get_trace_stack_layout(TraceLayout),
+	(
+		{ TraceLayout = yes }
+	->
+		stack_layout__construct_trace_rvals(MaybeEntryInfo,
+			MaybeExitInfo, TraceRvals)
+	;
+		{ TraceRvals = [] }
+	),
+
+	{ list__append(MaybeRvals0, TraceRvals, MaybeRvals) },
+
 	{ CModule = c_data(ModuleName, stack_layout(Label), yes, 
 		MaybeRvals, []) },
 	stack_layout__add_cmodule(CModule).
@@ -171,38 +214,95 @@
 		stack_layout_info, stack_layout_info).
 :- mode stack_layout__construct_internal_layout(in, in, in, out) is det.
 stack_layout__construct_internal_layout(ProcLabel, Label - Internal) -->
-	{ Internal = internal_layout_info(ContinuationLabelInfo) },
-	{
-		ContinuationLabelInfo = yes(continuation_label_info(
-			LiveLvalSet0, _TVars))
-	->
-		LiveLvalSet = LiveLvalSet0
-	;
-		% We record no live values here. This might not be
-		% true, however this label is not being used as a
-		% continuation, so it shouldn't be relied upon.
-		
-		set__init(LiveLvalSet)
-	},
-		
-		% XXX Should also output TVars.
-
-	{ set__to_sorted_list(LiveLvalSet, LiveLvals) },
-	
 		% generate the required rvals
 	stack_layout__get_module_name(ModuleName),
 	{ EntryAddrRval = const(data_addr_const(data_addr(ModuleName,
 		stack_layout(local(ProcLabel))))) },
+
+	stack_layout__construct_agc_rvals(Internal, AgcRvals),
+
+	{ LayoutRvals = [yes(EntryAddrRval) | AgcRvals] }, 
+
+	{ 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.
+stack_layout__construct_trace_rvals(MaybeEntryInfo, MaybeExitInfo,
+		RvalList) -->
+	( 
+		{ MaybeEntryInfo = yes(EntryInfo) },
+		{ MaybeExitInfo = yes(ExitInfo) }
+	->
+		{ EntryInfo = continuation_label_info(EntryLvals, EntryTVars) },
+		{ ExitInfo = continuation_label_info(ExitLvals, ExitTVars) },
+		stack_layout__construct_livelval_rvals(EntryLvals, EntryTVars,
+			EntryRvals),
+		stack_layout__construct_livelval_rvals(ExitLvals, ExitTVars,
+			ExitRvals),
+		{ list__append(EntryRvals, ExitRvals, RvalList) }
+	;
+		{ error("stack_layout__construct_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.
+stack_layout__construct_agc_rvals(Internal, RvalList) -->
+	stack_layout__get_agc_stack_layout(AgcStackLayout),
+	( 
+		{ AgcStackLayout = yes }
+	->
+		{ Internal = internal_layout_info(ContinuationLabelInfo) },
+		{
+			ContinuationLabelInfo = yes(continuation_label_info(
+				LiveLvalSet0, TVars0))
+		->
+			LiveLvalSet = LiveLvalSet0,
+			TVars = TVars0
+		;
+			% We record no live values here. This might not be
+			% true, however this label is not being used as a
+			% continuation, so it shouldn't be relied upon.
+			
+			set__init(LiveLvalSet),
+			set__init(TVars)
+		},
+		stack_layout__construct_livelval_rvals(LiveLvalSet, TVars,
+			RvalList)
+	;
+		{ RvalList = [yes(const(int_const(0))), 
+			yes(const(int_const(0)))] }
+	).
+
+
+	% XXX Should also create Tvars.
+
+:- pred stack_layout__construct_livelval_rvals(set(pair(lval, live_value_type)),
+		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),
 
-	{ MaybeRvals = [yes(EntryAddrRval), 
-		yes(LengthRval), yes(LiveValRval)]  },
+		% 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)] }.
+
 
-	{ CModule = c_data(ModuleName, stack_layout(Label), yes, 
-		MaybeRvals, []) },
-	stack_layout__add_cmodule(CModule).
 
 %---------------------------------------------------------------------------%
 
@@ -367,40 +467,53 @@
 		stack_layout_info).
 :- mode stack_layout__get_module_name(out, in, 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, 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),
+	LayoutInfo0 = stack_layout_info(A, CNum0, C, D, E),
 	CNum is CNum0 + 1,
-	LayoutInfo = stack_layout_info(A, CNum, C).
+	LayoutInfo = stack_layout_info(A, CNum, C, D, E).
 
 :- 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), 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, 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, _, _).
+
+:- 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, _).
 
 :- 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, CModules0),
+	LayoutInfo0 = stack_layout_info(A, B, C, D, CModules0),
 	CModules = [CModule | CModules0],
-	LayoutInfo = stack_layout_info(A, B, CModules).
+	LayoutInfo = stack_layout_info(A, B, C, D, CModules).
 
 :- 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),
-	LayoutInfo = stack_layout_info(A, CNum, C).
+	LayoutInfo0 = stack_layout_info(A, _, C, D, E),
+	LayoutInfo = stack_layout_info(A, CNum, C, D, E).
 
Index: compiler/unused_args.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/unused_args.m,v
retrieving revision 1.41
diff -u -r1.41 unused_args.m
--- unused_args.m	1998/01/13 10:13:57	1.41
+++ unused_args.m	1998/01/14 05:43:06
@@ -20,7 +20,8 @@
 %	- used to instantiate an output variable
 %	- involved in a simple test, switch or a semidet deconstruction 
 %	- used as an argument to another predicate in this module which is used.
-%  In accurate gc grades, the following variables are also considered used
+%  When using alternate liveness calculation, the following variables are 
+%  also considered used
 %	- a type-info (or part of a type-info) of a type parameter of the 
 %	  type of a variable that is used (for example, if a variable
 %	  of type list(T) is used, then TypeInfo_for_T is used)
@@ -253,8 +254,9 @@
 			ArgModes, VarDep1, VarDep2),
 		
 		module_info_globals(ModuleInfo, Globals),
-		globals__get_gc_method(Globals, GCMethod),
-		( GCMethod = accurate ->
+		globals__lookup_bool_option(Globals, alternate_liveness, 
+			AlternateLiveness),
+		( AlternateLiveness = yes ->
 			proc_info_typeinfo_varmap(ProcInfo, TVarMap),
 			setup_typeinfo_deps(Vars, VarTypes, 
 				proc(PredId, ProcId), TVarMap, VarDep2,


-- 
       Tyson Dowd           # 
                            #  Surreal humour isn't eveyone's cup of
     trd at cs.mu.oz.au        #  fur.
http://www.cs.mu.oz.au/~trd #



More information about the developers mailing list