for review: new method of handling failures, part 6 of 6

Zoltan Somogyi zs at cs.mu.OZ.AU
Thu Jul 2 16:25:25 AEST 1998


Index: compiler/lookup_switch.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/lookup_switch.m,v
retrieving revision 1.30
diff -u -r1.30 lookup_switch.m
--- lookup_switch.m	1998/03/03 17:34:57	1.30
+++ lookup_switch.m	1998/03/05 07:46:58
@@ -59,9 +59,9 @@
 
 :- pred lookup_switch__generate(var, list(var), case_consts,
 		int, int, can_fail, can_fail, maybe(set(var)), store_map,
-		code_tree, code_info, code_info).
+		branch_end, branch_end, code_tree, code_info, code_info).
 :- mode lookup_switch__generate(in, in, in, in, in, in, in, in, in,
-		out, in, out) is det.
+		in, out, out, in, out) is det.
 
 %-----------------------------------------------------------------------------%
 
@@ -200,13 +200,13 @@
 lookup_switch__generate_constants([Case|Cases], Vars, CodeModel,
 		[CaseVal|Rest], yes(Liveness)) -->
 	{ Case = case(_, int_constant(CaseTag), _, Goal) },
-	code_info__grab_code_info(CodeInfo),
+	code_info__remember_position(BranchStart),
 	code_gen__generate_goal(CodeModel, Goal, Code),
 	code_info__get_forward_live_vars(Liveness),
 	{ tree__is_empty(Code) },
 	lookup_switch__get_case_rvals(Vars, CaseRvals),
 	{ CaseVal = CaseTag - CaseRvals },
-	code_info__slap_code_info(CodeInfo),
+	code_info__reset_to_position(BranchStart),
 	lookup_switch__generate_constants(Cases, Vars, CodeModel, Rest, _).
 
 %---------------------------------------------------------------------------%
@@ -263,7 +263,7 @@
 
 lookup_switch__generate(Var, OutVars, CaseValues,
 		StartVal, EndVal, NeedRangeCheck, NeedBitVecCheck,
-		MLiveness, StoreMap, Code) -->
+		MLiveness, StoreMap, MaybeEnd0, MaybeEnd, Code) -->
 		% Evaluate the variable which we are going to be switching on
 	code_info__produce_variable(Var, VarCode, Rval),
 		% If the case values start at some number other than 0,
@@ -307,7 +307,8 @@
 		{ MLiveness = no },
 		{ error("lookup_switch__generate: no liveness!") }
 	),
-	code_info__generate_branch_end(model_det, StoreMap, LookupCode),
+	code_info__generate_branch_end(StoreMap, MaybeEnd0, MaybeEnd,
+		LookupCode),
 		% Assemble to code together
 	{ Comment = node([comment("lookup switch") - ""]) },
 	{ Code =
Index: compiler/mercury_compile.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/mercury_compile.m,v
retrieving revision 1.101
diff -u -r1.101 mercury_compile.m
--- mercury_compile.m	1998/07/01 04:09:37	1.101
+++ mercury_compile.m	1998/07/02 04:19:14
@@ -1153,7 +1153,7 @@
 	{ module_info_get_continuation_info(ModuleInfo3, ContInfo0) },
 	{ module_info_get_cell_count(ModuleInfo3, CellCount0) },
 	{ generate_proc_code(ProcInfo7, ProcId, PredId, ModuleInfo3, Globals,
-		ContInfo0, CellCount0, ContInfo1, CellCount, Proc0) },
+		ContInfo0, ContInfo1, CellCount0, CellCount, Proc0) },
 	{ module_info_set_continuation_info(ModuleInfo3, ContInfo1, 
 		ModuleInfo4) },
 	{ module_info_set_cell_count(ModuleInfo4, CellCount, ModuleInfo5) },
Index: compiler/middle_rec.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/middle_rec.m,v
retrieving revision 1.72
diff -u -r1.72 middle_rec.m
--- middle_rec.m	1998/06/09 02:13:49	1.72
+++ middle_rec.m	1998/06/29 08:17:32
@@ -125,22 +125,24 @@
 	{ tree__flatten(EntryTestCode, EntryTestListList) },
 	{ list__condense(EntryTestListList, EntryTestList) },
 
-	code_info__grab_code_info(CodeInfo),
+	code_info__remember_position(BranchStart),
 	code_gen__generate_goal(model_det, Base, BaseGoalCode),
-	code_info__generate_branch_end(model_det, StoreMap, BaseSaveCode),
-	code_info__slap_code_info(CodeInfo),
+	code_info__generate_branch_end(StoreMap, no, MaybeEnd1,
+		BaseSaveCode),
+	code_info__reset_to_position(BranchStart),
 	code_gen__generate_goal(model_det, Recursive, RecGoalCode),
-	code_info__generate_branch_end(model_det, StoreMap, RecSaveCode),
+	code_info__generate_branch_end(StoreMap, MaybeEnd1, MaybeEnd,
+		RecSaveCode),
 
 	code_info__post_goal_update(SwitchGoalInfo),
-	code_info__remake_with_store_map(StoreMap),
+	code_info__after_all_branches(StoreMap, MaybeEnd),
 
 	code_info__get_arginfo(ArgModes),
 	code_info__get_headvars(HeadVars),
 	{ assoc_list__from_corresponding_lists(HeadVars, ArgModes, Args) },
 	code_info__setup_call(Args, callee, EpilogCode),
 
-	{ code_gen__output_args(Args, LiveArgs) },
+	{ code_util__output_args(Args, LiveArgs) },
 
 	{ BaseCode = tree(BaseGoalCode, tree(BaseSaveCode, EpilogCode)) },
 	{ RecCode = tree(RecGoalCode, tree(RecSaveCode, EpilogCode)) },
@@ -390,7 +392,7 @@
 	middle_rec__find_used_registers_lval(Lval, Used0, Used1),
 	middle_rec__find_used_registers_rval(Rval, Used1, Used).
 middle_rec__find_used_registers_instr(call(_, _, _, _), Used, Used).
-middle_rec__find_used_registers_instr(mkframe(_, _, _, _), Used, Used).
+middle_rec__find_used_registers_instr(mkframe(_, _), Used, Used).
 middle_rec__find_used_registers_instr(modframe(_), Used, Used).
 middle_rec__find_used_registers_instr(label(_), Used, Used).
 middle_rec__find_used_registers_instr(goto(_), Used, Used).
Index: compiler/opt_debug.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/opt_debug.m,v
retrieving revision 1.82
diff -u -r1.82 opt_debug.m
--- opt_debug.m	1998/06/09 02:14:06	1.82
+++ opt_debug.m	1998/06/29 08:39:27
@@ -298,7 +298,7 @@
 	opt_debug__dump_code_addr(Proc, P_str),
 	opt_debug__dump_code_addr(Ret, R_str),
 	string__append_list(["call(", P_str, ", ", R_str, ")"], Str).
-opt_debug__dump_vninstr(vn_mkframe(_, _, _, _), "mkframe").
+opt_debug__dump_vninstr(vn_mkframe(_, _), "mkframe").
 opt_debug__dump_vninstr(vn_label(Label), Str) :-
 	opt_debug__dump_label(Label, L_str),
 	string__append_list(["label(", L_str, ")"], Str).
@@ -503,6 +503,9 @@
 opt_debug__dump_vnlval(vn_succfr(V), Str) :-
 	string__int_to_string(V, V_str),
 	string__append_list(["vn_succfr(", V_str, ")"], Str).
+opt_debug__dump_vnlval(vn_redofr(V), Str) :-
+	string__int_to_string(V, V_str),
+	string__append_list(["vn_redofr(", V_str, ")"], Str).
 opt_debug__dump_vnlval(vn_redoip(V), Str) :-
 	string__int_to_string(V, V_str),
 	string__append_list(["vn_redoip(", V_str, ")"], Str).
@@ -587,6 +590,9 @@
 opt_debug__dump_lval(prevfr(R), Str) :-
 	opt_debug__dump_rval(R, R_str),
 	string__append_list(["prevfr(", R_str, ")"], Str).
+opt_debug__dump_lval(redofr(R), Str) :-
+	opt_debug__dump_rval(R, R_str),
+	string__append_list(["redofr(", R_str, ")"], Str).
 opt_debug__dump_lval(redoip(R), Str) :-
 	opt_debug__dump_rval(R, R_str),
 	string__append_list(["redoip(", R_str, ")"], Str).
@@ -835,17 +841,23 @@
 	opt_debug__dump_code_addr(Proc, P_str),
 	opt_debug__dump_code_addr(Ret, R_str),
 	string__append_list(["call(", P_str, ", ", R_str, ", ...)"], Str).
-opt_debug__dump_instr(mkframe(Name, Size, MaybePragma, Redoip), Str) :-
-	string__int_to_string(Size, S_str),
-	( MaybePragma = yes(pragma_c_struct(StructName, StructFields, _)) ->
-		string__append_list(["yes(", StructName, ", ",
-			StructFields, ")"], P_str)
-	;
-		P_str = "no"
-	),
+opt_debug__dump_instr(mkframe(FrameInfo, Redoip), Str) :-
 	opt_debug__dump_code_addr(Redoip, R_str),
-	string__append_list(["mkframe(", Name, ", ", S_str, ", ",
-		P_str, ", ", R_str, ")"], Str).
+	(
+		FrameInfo = ordinary_frame(Name, Size, MaybePragma),
+		string__int_to_string(Size, S_str),
+		( MaybePragma = yes(pragma_c_struct(StructName, Fields, _)) ->
+			string__append_list(["yes(", StructName, ", ",
+				Fields, ")"], P_str)
+		;
+			P_str = "no"
+		),
+		string__append_list(["mkframe(", Name, ", ", S_str, ", ",
+			P_str, ", ", R_str, ")"], Str)
+	;
+		FrameInfo = temp_frame,
+		string__append_list(["mktempframe(", R_str, ")"], Str)
+	).
 opt_debug__dump_instr(modframe(Redoip), Str) :-
 	opt_debug__dump_code_addr(Redoip, R_str),
 	string__append_list(["modframe(", R_str, ")"], Str).
Index: compiler/opt_util.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/opt_util.m,v
retrieving revision 1.93
diff -u -r1.93 opt_util.m
--- opt_util.m	1998/06/09 02:14:09	1.93
+++ opt_util.m	1998/06/29 07:33:33
@@ -406,7 +406,7 @@
 		list__reverse(RevSkip, Skip),
 		Rest = Instrs
 	;
-		Uinstr = mkframe(_, _, _, _)
+		Uinstr = mkframe(_, _)
 	->
 		fail
 	;
@@ -639,16 +639,10 @@
 opt_util__lval_refers_stackvars(maxfr, no).
 opt_util__lval_refers_stackvars(curfr, no).
 opt_util__lval_refers_stackvars(succfr(Rval), Refers) :-
-	%% I'm not 100% sure of what we should do here, so
-	%% to be safe, just abort. I don't think this code
-	%% is used anyway. -fjh.
-	% error("found succfr in lval_refers_stackvars").
 	opt_util__rval_refers_stackvars(Rval, Refers).
 opt_util__lval_refers_stackvars(prevfr(Rval), Refers) :-
-	%% I'm not 100% sure of what we should do here, so
-	%% to be safe, just abort. I don't think this code
-	%% is used anyway. -fjh.
-	%error("found prevfr in lval_refers_stackvars").
+	opt_util__rval_refers_stackvars(Rval, Refers).
+opt_util__lval_refers_stackvars(redofr(Rval), Refers) :-
 	opt_util__rval_refers_stackvars(Rval, Refers).
 opt_util__lval_refers_stackvars(redoip(Rval), Refers) :-
 	opt_util__rval_refers_stackvars(Rval, Refers).
@@ -781,7 +775,7 @@
 		Uinstr0 = call(_, _, _, _),
 		Need = no
 	;
-		Uinstr0 = mkframe(_, _, _, _),
+		Uinstr0 = mkframe(_, _),
 		Need = no
 	;
 		Uinstr0 = modframe(_),
@@ -986,7 +980,7 @@
 opt_util__can_instr_branch_away(block(_, _, _), yes).
 opt_util__can_instr_branch_away(assign(_, _), no).
 opt_util__can_instr_branch_away(call(_, _, _, _), yes).
-opt_util__can_instr_branch_away(mkframe(_, _, _, _), no).
+opt_util__can_instr_branch_away(mkframe(_, _), no).
 opt_util__can_instr_branch_away(modframe(_), no).
 opt_util__can_instr_branch_away(label(_), no).
 opt_util__can_instr_branch_away(goto(_), yes).
@@ -1049,7 +1043,7 @@
 	opt_util__can_block_fall_through(Instrs, FallThrough).
 opt_util__can_instr_fall_through(assign(_, _), yes).
 opt_util__can_instr_fall_through(call(_, _, _, _), no).
-opt_util__can_instr_fall_through(mkframe(_, _, _, _), yes).
+opt_util__can_instr_fall_through(mkframe(_, _), yes).
 opt_util__can_instr_fall_through(modframe(_), yes).
 opt_util__can_instr_fall_through(label(_), yes).
 opt_util__can_instr_fall_through(goto(_), no).
@@ -1094,7 +1088,7 @@
 opt_util__can_use_livevals(block(_, _, _), no).
 opt_util__can_use_livevals(assign(_, _), no).
 opt_util__can_use_livevals(call(_, _, _, _), yes).
-opt_util__can_use_livevals(mkframe(_, _, _, _), no).
+opt_util__can_use_livevals(mkframe(_, _), no).
 opt_util__can_use_livevals(modframe(_), no).
 opt_util__can_use_livevals(label(_), no).
 opt_util__can_use_livevals(goto(_), yes).
@@ -1156,7 +1150,7 @@
 	opt_util__instr_list_labels(Instrs, Labels, CodeAddrs).
 opt_util__instr_labels_2(assign(_,_), [], []).
 opt_util__instr_labels_2(call(Target, Ret, _, _), [], [Target, Ret]).
-opt_util__instr_labels_2(mkframe(_, _, _, Addr), [], [Addr]).
+opt_util__instr_labels_2(mkframe(_, Addr), [], [Addr]).
 opt_util__instr_labels_2(modframe(Addr), [], [Addr]).
 opt_util__instr_labels_2(label(_), [], []).
 opt_util__instr_labels_2(goto(Addr), [], [Addr]).
@@ -1195,7 +1189,7 @@
 	opt_util__instr_list_rvals_and_lvals(Instrs, Labels, CodeAddrs).
 opt_util__instr_rvals_and_lvals(assign(Lval,Rval), [Rval], [Lval]).
 opt_util__instr_rvals_and_lvals(call(_, _, _, _), [], []).
-opt_util__instr_rvals_and_lvals(mkframe(_, _, _, _), [], []).
+opt_util__instr_rvals_and_lvals(mkframe(_, _), [], []).
 opt_util__instr_rvals_and_lvals(modframe(_), [], []).
 opt_util__instr_rvals_and_lvals(label(_), [], []).
 opt_util__instr_rvals_and_lvals(goto(_), [], []).
@@ -1318,7 +1312,7 @@
 	opt_util__count_temps_lval(Lval, R0, R1, F0, F1),
 	opt_util__count_temps_rval(Rval, R1, R, F1, F).
 opt_util__count_temps_instr(call(_, _, _, _), R, R, F, F).
-opt_util__count_temps_instr(mkframe(_, _, _, _), R, R, F, F).
+opt_util__count_temps_instr(mkframe(_, _), R, R, F, F).
 opt_util__count_temps_instr(modframe(_), R, R, F, F).
 opt_util__count_temps_instr(label(_), R, R, F, F).
 opt_util__count_temps_instr(goto(_), R, R, F, F).
@@ -1476,6 +1470,7 @@
 opt_util__touches_nondet_ctrl_lval(curfr, yes).
 opt_util__touches_nondet_ctrl_lval(succfr(_), yes).
 opt_util__touches_nondet_ctrl_lval(prevfr(_), yes).
+opt_util__touches_nondet_ctrl_lval(redofr(_), yes).
 opt_util__touches_nondet_ctrl_lval(redoip(_), yes).
 opt_util__touches_nondet_ctrl_lval(succip(_), yes).
 opt_util__touches_nondet_ctrl_lval(hp, no).
@@ -1551,6 +1546,7 @@
 opt_util__lval_access_rvals(curfr, []).
 opt_util__lval_access_rvals(redoip(Rval), [Rval]).
 opt_util__lval_access_rvals(succip(Rval), [Rval]).
+opt_util__lval_access_rvals(redofr(Rval), [Rval]).
 opt_util__lval_access_rvals(prevfr(Rval), [Rval]).
 opt_util__lval_access_rvals(succfr(Rval), [Rval]).
 opt_util__lval_access_rvals(hp, []).
Index: compiler/options.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/options.m,v
retrieving revision 1.235
diff -u -r1.235 options.m
--- options.m	1998/07/01 06:08:27	1.235
+++ options.m	1998/07/01 12:22:06
@@ -249,6 +249,7 @@
 		;	middle_rec
 		;	simple_neg
 		;	follow_vars
+		;	allow_hijacks
 	%	- LLDS
 		;	optimize
 		;	optimize_peep
@@ -553,6 +554,7 @@
 	middle_rec		-	bool(no),
 	simple_neg		-	bool(no),
 	follow_vars		-	bool(no),
+	allow_hijacks		-	bool(yes),
 
 % LLDS
 	optimize		-	bool(no),
@@ -870,6 +872,7 @@
 long_option("middle-rec",		middle_rec).
 long_option("simple_neg",		simple_neg).
 long_option("follow-vars",		follow_vars).
+long_option("allow-hijacks",		allow_hijacks).
 
 % LLDS optimizations
 long_option("llds-optimize",		optimize).
@@ -1849,6 +1852,10 @@
 	io__write_string("\t\tDon't generate simplified code for simple negations.\n"),
 	io__write_string("\t--no-follow-vars\n"),
 	io__write_string("\t\tDon't optimize the assignment of registers in branched goals.\n").
+%	io__write_string("\t--no-allow-hijacks\n"),
+%	io__write_string("\t\tDo not generate code in which a procedure hijacks\n"),
+%	io__write_string("\t\ta nondet stack frame that possibly belongs to\n"),
+%	io__write_string("\t\tanother procedure invocation\n").
 
 :- pred options_help_llds_llds_optimization(io__state::di, io__state::uo) is det.
 
Index: compiler/par_conj_gen.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/par_conj_gen.m,v
retrieving revision 1.1
diff -u -r1.1 par_conj_gen.m
--- par_conj_gen.m	1998/06/09 03:19:02	1.1
+++ par_conj_gen.m	1998/06/09 10:17:50
@@ -93,9 +93,9 @@
 :- import_module hlds_goal, llds, code_info.
 :- import_module list.
 
-:- pred par_conj_gen__generate_det_par_conj(list(hlds_goal), hlds_goal_info,
-					code_tree, code_info, code_info).
-:- mode par_conj_gen__generate_det_par_conj(in, in, out, in, out) is det.
+:- pred par_conj_gen__generate_par_conj(list(hlds_goal), hlds_goal_info,
+				code_model, code_tree, code_info, code_info).
+:- mode par_conj_gen__generate_par_conj(in, in, in, out, in, out) is det.
 
 %---------------------------------------------------------------------------%
 
@@ -107,7 +107,16 @@
 
 %---------------------------------------------------------------------------%
 
-par_conj_gen__generate_det_par_conj(Goals, GoalInfo, Code) -->
+par_conj_gen__generate_par_conj(Goals, GoalInfo, CodeModel, Code) -->
+	{
+		CodeModel = model_det
+	;
+		CodeModel = model_semi,
+		error("sorry, semidet parallel conjunction not implemented")
+	;
+		CodeModel = model_non,
+		error("sorry, nondet parallel conjunction not implemented")
+	},
 	code_info__get_globals(Globals),
 	{ globals__lookup_int_option(Globals, sync_term_size, STSize) },
 	code_info__get_known_variables(Vars),
@@ -125,33 +134,35 @@
 	code_info__acquire_temp_slot(sync_term, SyncSlot),
 	code_info__acquire_temp_slot(lval(sp), SpSlot),
 	{ MakeTerm = node([
-		assign(SpSlot, lval(sp)) - "save the parent stack pointer",
+		assign(SpSlot, lval(sp))
+			- "save the parent stack pointer",
 		incr_hp(RegLval, no, const(int_const(STSize)),
 			"synchronization vector")
 			- "allocate a synchronization vector",
-		init_sync_term(RegLval, NumGoals) - "initialize sync term",
+		init_sync_term(RegLval, NumGoals)
+			- "initialize sync term",
 		assign(SyncSlot, lval(RegLval))
-				- "store the sync-term on the stack"
+			- "store the sync-term on the stack"
 	]) },
 	code_info__release_reg(RegLval),
 	code_info__clear_all_registers,
 	par_conj_gen__generate_det_par_conj_2(Goals, 0, SyncSlot, SpSlot,
-		Initial, GoalCode),
+		Initial, no, GoalCode),
 	code_info__release_temp_slot(SyncSlot),
 	{ Code = tree(tree(SaveCode, MakeTerm), GoalCode) },
 	code_info__clear_all_registers,
 	par_conj_gen__place_all_outputs(Outputs).
 
 :- pred par_conj_gen__generate_det_par_conj_2(list(hlds_goal), int, lval, lval,
-		instmap, code_tree, code_info, code_info).
-:- mode par_conj_gen__generate_det_par_conj_2(in, in, in, in, in,
-		out, in, out) is det.
+		instmap, branch_end, code_tree, code_info, code_info).
+:- mode par_conj_gen__generate_det_par_conj_2(in, in, in, in,
+		in, in, out, in, out) is det.
 
 par_conj_gen__generate_det_par_conj_2([], _N, _SyncTerm, _SpSlot, _Initial,
-		empty) --> [].
+		_, empty) --> [].
 par_conj_gen__generate_det_par_conj_2([Goal|Goals], N, SyncTerm, SpSlot,
-		Initial, Code) -->
-	code_info__grab_code_info(CodeInfo0),
+		Initial, MaybeEnd0, Code) -->
+	code_info__remember_position(StartPos),
 	code_info__get_next_label(ThisConjunct),
 	code_info__get_next_label(NextConjunct),
 	code_gen__generate_goal(model_det, Goal, ThisGoalCode),
@@ -159,7 +170,8 @@
 	code_info__get_known_variables(Variables),
 	{ set__list_to_set(Variables, LiveVars) },
 	{ map__select(AllSlots, LiveVars, StoreMap) },
-	code_info__generate_branch_end(model_det, StoreMap, SaveCode),
+	code_info__generate_branch_end(StoreMap, MaybeEnd0, MaybeEnd,
+		SaveCode),
 	{ Goal = _GoalExpr - GoalInfo },
 	{ goal_info_get_instmap_delta(GoalInfo, Delta) },
 	{ instmap__apply_instmap_delta(Initial, Delta, Final) },
@@ -170,16 +182,19 @@
 	(
 		{ Goals = [_|_] }
 	->
-		code_info__slap_code_info(CodeInfo0),
+		code_info__reset_to_position(StartPos),
 		code_info__get_total_stackslot_count(NumSlots),
 		{ ForkCode = node([
 			fork(ThisConjunct, NextConjunct, NumSlots)
 				- "fork off a child",
-			label(ThisConjunct) - "child thread"
+			label(ThisConjunct)
+				- "child thread"
 		]) },
 		{ JoinCode = node([
-			join_and_terminate(SyncTerm) - "finish",
-			label(NextConjunct) - "start of the next conjunct"
+			join_and_terminate(SyncTerm)
+				- "finish",
+			label(NextConjunct)
+				- "start of the next conjunct"
 		]) }
 	;
 		code_info__get_next_label(ContLab),
@@ -187,7 +202,8 @@
 		{ JoinCode = node([
 			join_and_continue(SyncTerm, ContLab)
 				- "sync with children then continue",
-			label(ContLab) - "end of parallel conjunction"
+			label(ContLab)
+				- "end of parallel conjunction"
 		]) }
 	),
 	{ ThisCode = tree(
@@ -196,7 +212,7 @@
 	) },
 	{ N1 is N + 1 },
 	par_conj_gen__generate_det_par_conj_2(Goals, N1, SyncTerm, SpSlot,
-			Initial, RestCode),
+			Initial, MaybeEnd, RestCode),
 	{ Code = tree(ThisCode, RestCode) }.
 
 :- pred par_conj_gen__find_outputs(list(var), instmap, instmap, module_info,
@@ -258,4 +274,3 @@
 		code_info__set_var_location(Var, Slot)
 	),
 	par_conj_gen__place_all_outputs(Vars).
-
Index: compiler/peephole.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/peephole.m,v
retrieving revision 1.74
diff -u -r1.74 peephole.m
--- peephole.m	1998/06/16 06:43:52	1.74
+++ peephole.m	1998/06/29 08:04:44
@@ -140,33 +140,33 @@
 	% This should also be done if the modframe appears instead as an
 	% assignment to the redoip of curfr or maxfr.
 	%
-	%	mkframe(D, S, _)	=>	mkframe(D, S, Redoip)
+	%	mkframe(NFI, _)		=>	mkframe(NFI, Redoip)
 	%	<straightline instrs>		<straightline instrs>
 	%	modframe(Redoip)
 	%
 	% If a `mkframe' is followed by a test that can fail, we try to
 	% swap the two instructions to avoid doing the mkframe unnecessarily.
 	%
-	%	mkframe(D, S, dofail)	=>	if_val(test, redo)
-	%	if_val(test, redo/fail)		mkframe(D, S, dofail)
+	%	mkframe(NFI, dofail)	=>	if_val(test, redo)
+	%	if_val(test, redo/fail)		mkframe(NFI, dofail)
 	%
-	%	mkframe(D, S, label)	=>	if_val(test, redo)
-	%	if_val(test, fail)		mkframe(D, S, label)
+	%	mkframe(NFI, label)	=>	if_val(test, redo)
+	%	if_val(test, fail)		mkframe(NFI, label)
 	%
-	%	mkframe(D, S, label)	=>	mkframe(D, S, label)
+	%	mkframe(NFI, label)	=>	mkframe(NFI, label)
 	%	if_val(test, redo)		if_val(test, label)
 	%
 	% These two patterns are mutually exclusive because if_val is not
 	% straight-line code.
 
-peephole__match(mkframe(Name, Slots, Pragma, Redoip1), Comment, _,
+peephole__match(mkframe(NondetFrameInfo, Redoip1), Comment, _,
 		Instrs0, Instrs) :-
 	(
 		opt_util__next_modframe(Instrs0, [], Redoip2, Skipped, Rest),
 		opt_util__touches_nondet_ctrl(Skipped, no)
 	->
 		list__append(Skipped, Rest, Instrs1),
-		Instrs = [mkframe(Name, Slots, Pragma, Redoip2) - Comment
+		Instrs = [mkframe(NondetFrameInfo, Redoip2) - Comment
 			| Instrs1]
 	;
 		opt_util__skip_comments_livevals(Instrs0, Instrs1),
@@ -177,8 +177,10 @@
 			( Target = do_redo ; Target = do_fail)
 		->
 			Instrs = [
-				if_val(Test, do_redo) - Comment2,
-				mkframe(Name, Slots, Pragma, do_fail) - Comment
+				if_val(Test, do_redo)
+					- Comment2,
+				mkframe(NondetFrameInfo, do_fail)
+					- Comment
 				| Instrs2
 			]
 		;
@@ -188,8 +190,9 @@
 				Target = do_fail
 			->
 				Instrs = [
-					if_val(Test, do_redo) - Comment2,
-					mkframe(Name, Slots, Pragma, Redoip1)
+					if_val(Test, do_redo)
+						- Comment2,
+					mkframe(NondetFrameInfo, Redoip1)
 						- Comment
 					| Instrs2
 				]
@@ -197,9 +200,10 @@
 				Target = do_redo
 			->
 				Instrs = [
-					mkframe(Name, Slots, Pragma, Redoip1)
+					mkframe(NondetFrameInfo, Redoip1)
 						- Comment,
-					if_val(Test, Redoip1) - Comment2
+					if_val(Test, Redoip1)
+						- Comment2
 					| Instrs2
 				]
 			;
Index: compiler/stack_layout.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/stack_layout.m,v
retrieving revision 1.14
diff -u -r1.14 stack_layout.m
--- stack_layout.m	1998/06/18 06:06:49	1.14
+++ stack_layout.m	1998/06/18 06:10:36
@@ -633,10 +633,12 @@
 	{ Rval = const(int_const(2)) }.
 stack_layout__represent_live_value_type(maxfr, Rval) -->
 	{ Rval = const(int_const(3)) }.
-stack_layout__represent_live_value_type(redoip, Rval) -->
+stack_layout__represent_live_value_type(redofr, Rval) -->
 	{ Rval = const(int_const(4)) }.
-stack_layout__represent_live_value_type(unwanted, Rval) -->
+stack_layout__represent_live_value_type(redoip, Rval) -->
 	{ Rval = const(int_const(5)) }.
+stack_layout__represent_live_value_type(unwanted, Rval) -->
+	{ Rval = const(int_const(6)) }.
 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,
@@ -680,6 +682,8 @@
 stack_layout__represent_lval(succip(_), _) :-
 	error("stack_layout: continuation live value stored in code address").
 stack_layout__represent_lval(redoip(_), _) :-
+	error("stack_layout: continuation live value stored in code address").
+stack_layout__represent_lval(redofr(_), _) :-
 	error("stack_layout: continuation live value stored in code address").
 stack_layout__represent_lval(succfr(_), _) :-
 	error("stack_layout: continuation live value stored in code address").
Index: compiler/string_switch.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/string_switch.m,v
retrieving revision 1.29
diff -u -r1.29 string_switch.m
--- string_switch.m	1998/04/08 11:32:25	1.29
+++ string_switch.m	1998/05/17 03:53:46
@@ -21,8 +21,9 @@
 :- import_module term.
 
 :- pred string_switch__generate(cases_list, var, code_model,
-	can_fail, store_map, label, code_tree, code_info, code_info).
-:- mode string_switch__generate(in, in, in, in, in, in, out, in, out)
+	can_fail, store_map, label, branch_end, branch_end, code_tree,
+	code_info, code_info).
+:- mode string_switch__generate(in, in, in, in, in, in, in, out, out, in, out)
 	is det.
 
 %-----------------------------------------------------------------------------%
@@ -33,7 +34,7 @@
 :- import_module bool, int, string, list, map, std_util, assoc_list, require.
 
 string_switch__generate(Cases, Var, CodeModel, _CanFail, StoreMap,
-		EndLabel, Code) -->
+		EndLabel, MaybeEnd0, MaybeEnd, Code) -->
 	code_info__produce_variable(Var, VarCode, VarRval),
 	code_info__acquire_reg(r, SlotReg),
 	code_info__acquire_reg(r, StringReg),
@@ -67,7 +68,7 @@
 		% before the code for the cases (which might reuse those
 		% registers), and because that code is generated manually
 		% (below) so we don't need the reg info to be valid when
-		% we generated it.
+		% we generate it.
 	code_info__release_reg(SlotReg),
 	code_info__release_reg(StringReg),
 
@@ -80,8 +81,8 @@
 		% Generate the code etc. for the hash table
 		%
 	string_switch__gen_hash_slots(0, TableSize, HashSlotsMap, CodeModel,
-		StoreMap, FailLabel, EndLabel, Strings, Labels,
-		NextSlots, SlotsCode),
+		StoreMap, FailLabel, EndLabel, MaybeEnd0, MaybeEnd,
+		Strings, Labels, NextSlots, SlotsCode),
 
 		% Generate code which does the hash table lookup
 	{
@@ -245,16 +246,18 @@
 	).
 
 :- pred string_switch__gen_hash_slots(int, int, map(int, hash_slot),
-	code_model, store_map, label, label, list(maybe(rval)), list(label),
-	list(maybe(rval)), code_tree, code_info, code_info).
+	code_model, store_map, label, label, branch_end, branch_end,
+	list(maybe(rval)), list(label), list(maybe(rval)), code_tree,
+	code_info, code_info).
 :- mode string_switch__gen_hash_slots(in, in, in, in, in, in, in,
-	out, out, out, out, in, out) is det.
+	in, out, out, out, out, out, in, out) is det.
 
 string_switch__gen_hash_slots(Slot, TableSize, HashSlotMap, CodeModel,
-		StoreMap, FailLabel, EndLabel, Strings, Labels,
-		NextSlots, Code) -->
+		StoreMap, FailLabel, EndLabel, MaybeEnd0, MaybeEnd,
+		Strings, Labels, NextSlots, Code) -->
 	( { Slot = TableSize } ->
 		{
+			MaybeEnd = MaybeEnd0,
 			Strings = [],
 			Labels = [],
 			NextSlots = [],
@@ -264,8 +267,9 @@
 		}
 	;
 		string_switch__gen_hash_slot(Slot, TableSize, HashSlotMap,
-				CodeModel, StoreMap, FailLabel, EndLabel,
-				String, Label, NextSlot, SlotCode),
+			CodeModel, StoreMap, FailLabel, EndLabel,
+			MaybeEnd0, MaybeEnd1,
+			String, Label, NextSlot, SlotCode),
 		{ Slot1 is Slot + 1 },
 		{ 
 			Strings = [String | Strings0],
@@ -274,19 +278,21 @@
 			Code = tree(SlotCode, Code0)
 		},
 		string_switch__gen_hash_slots(Slot1, TableSize, HashSlotMap,
-				CodeModel, StoreMap, FailLabel, EndLabel,
-				Strings0, Labels0, NextSlots0, Code0)
+			CodeModel, StoreMap, FailLabel, EndLabel,
+			MaybeEnd1, MaybeEnd,
+			Strings0, Labels0, NextSlots0, Code0)
 	).
 
 :- pred string_switch__gen_hash_slot(int, int, map(int, hash_slot),
-	code_model, store_map, label, label, maybe(rval), label,
-	maybe(rval), code_tree, code_info, code_info).
+	code_model, store_map, label, label, branch_end, branch_end,
+	maybe(rval), label, maybe(rval), code_tree,
+	code_info, code_info).
 :- mode string_switch__gen_hash_slot(in, in, in, in, in, in, in,
-	out, out, out, out, in, out) is det.
+	in, out, out, out, out, out, in, out) is det.
 
 string_switch__gen_hash_slot(Slot, TblSize, HashSlotMap, CodeModel, StoreMap,
-		FailLabel, EndLabel, yes(StringRval), Label,
-		yes(NextSlotRval), Code) -->
+		FailLabel, EndLabel, MaybeEnd0, MaybeEnd,
+		yes(StringRval), Label, yes(NextSlotRval), Code) -->
 	(
 		{ map__search(HashSlotMap, Slot, hash_slot(Case, Next)) }
 	->
@@ -303,17 +309,18 @@
 		{ LabelCode = node([
 			label(Label) - Comment
 		]) },
-		code_info__grab_code_info(CodeInfo),
+		code_info__remember_position(BranchStart),
 		trace__maybe_generate_internal_event_code(Goal, TraceCode),
 		code_gen__generate_goal(CodeModel, Goal, GoalCode),
-		code_info__generate_branch_end(CodeModel, StoreMap, SaveCode),
+		code_info__generate_branch_end(StoreMap, MaybeEnd0, MaybeEnd,
+			SaveCode),
 		(
 			{ string_switch__this_is_last_case(Slot, TblSize,
 				HashSlotMap) }
 		->
 			[]
 		;
-			code_info__slap_code_info(CodeInfo)
+			code_info__reset_to_position(BranchStart)
 		),
 		{ FinishCode = node([
 			goto(label(EndLabel)) - "jump to end of switch"
@@ -326,6 +333,7 @@
 			     FinishCode))))
 		}
 	;
+		{ MaybeEnd = MaybeEnd0 },
 		{ StringRval = const(int_const(0)) },
 		{ Label = FailLabel },
 		{ NextSlotRval = const(int_const(-2)) },
Index: compiler/switch_gen.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/switch_gen.m,v
retrieving revision 1.65
diff -u -r1.65 switch_gen.m
--- switch_gen.m	1998/04/08 11:32:28	1.65
+++ switch_gen.m	1998/05/17 04:26:56
@@ -105,8 +105,8 @@
 			OutVars, CaseVals, MLiveness)
 	->
 		lookup_switch__generate(CaseVar, OutVars, CaseVals,
-			FirstVal, LastVal, NeedRangeCheck,
-			NeedBitVecCheck, MLiveness, StoreMap, Code)
+			FirstVal, LastVal, NeedRangeCheck, NeedBitVecCheck,
+			MLiveness, StoreMap, no, MaybeEnd, Code)
 	;
 		{ Indexing = yes },
 		{ SwitchCategory = atomic_switch },
@@ -121,7 +121,7 @@
 	->
 		dense_switch__generate(TaggedCases,
 			FirstVal, LastVal, CaseVar, CodeModel, CanFail1,
-			StoreMap, EndLabel, Code)
+			StoreMap, EndLabel, no, MaybeEnd, Code)
 	;
 		{ Indexing = yes },
 		{ SwitchCategory = string_switch },
@@ -131,7 +131,7 @@
 		{ NumCases >= StringSize }
 	->
 		string_switch__generate(TaggedCases, CaseVar, CodeModel,
-			CanFail, StoreMap, EndLabel, Code)
+			CanFail, StoreMap, EndLabel, no, MaybeEnd, Code)
 	;
 		{ Indexing = yes },
 		{ SwitchCategory = tag_switch },
@@ -141,16 +141,17 @@
 		{ NumCases >= TagSize }
 	->
 		tag_switch__generate(TaggedCases, CaseVar, CodeModel, CanFail,
-			StoreMap, EndLabel, Code)
+			StoreMap, EndLabel, no, MaybeEnd, Code)
 	;
 		% To generate a switch, first we flush the
 		% variable on whose tag we are going to switch, then we
 		% generate the cases for the switch.
 
 		switch_gen__generate_all_cases(TaggedCases, CaseVar,
-			CodeModel, CanFail, StoreMap, EndLabel, Code)
+			CodeModel, CanFail, StoreMap, EndLabel, no, MaybeEnd,
+			Code)
 	),
-	code_info__remake_with_store_map(StoreMap).
+	code_info__after_all_branches(StoreMap, MaybeEnd).
 
 %---------------------------------------------------------------------------%
 
@@ -243,12 +244,13 @@
 	% breaks caused by taken branches.
 
 :- pred switch_gen__generate_all_cases(list(extended_case), var, code_model,
-	can_fail, store_map, label, code_tree, code_info, code_info).
-:- mode switch_gen__generate_all_cases(in, in, in, in, in, in, out, in, out)
-	is det.
+	can_fail, store_map, label, branch_end, branch_end, code_tree,
+	code_info, code_info).
+:- mode switch_gen__generate_all_cases(in, in, in, in, in, in, in, out, out,
+	in, out) is det.
 
 switch_gen__generate_all_cases(Cases0, Var, CodeModel, CanFail, StoreMap,
-		EndLabel, Code) -->
+		EndLabel, MaybeEnd0, MaybeEnd, Code) -->
 	code_info__produce_variable(Var, VarCode, _Rval),
 	(
 		{ CodeModel = model_det },
@@ -275,25 +277,26 @@
 			Cases = [Case2, Case1]
 		;
 			Cases = Cases0
-		},
-		switch_gen__generate_cases(Cases, Var, CodeModel, CanFail,
-			StoreMap, EndLabel, CasesCode)
+		}
 	;
-		switch_gen__generate_cases(Cases0, Var, CodeModel, CanFail,
-			StoreMap, EndLabel, CasesCode)
+		{ Cases = Cases0 }
 	),
+	switch_gen__generate_cases(Cases, Var, CodeModel, CanFail,
+		StoreMap, EndLabel, MaybeEnd0, MaybeEnd, CasesCode),
 	{ Code = tree(VarCode, CasesCode) }.
 
 :- pred switch_gen__generate_cases(list(extended_case), var, code_model,
-	can_fail, store_map, label, code_tree, code_info, code_info).
-:- mode switch_gen__generate_cases(in, in, in, in, in, in, out, in, out) is det.
+	can_fail, store_map, label, branch_end, branch_end, code_tree,
+	code_info, code_info).
+:- mode switch_gen__generate_cases(in, in, in, in, in, in, in, out, out,
+	in, out) is det.
 
 	% At the end of a locally semidet switch, we fail because we
 	% came across a tag which was not covered by one of the cases.
 	% It is followed by the end of switch label to which the cases
 	% branch.
 switch_gen__generate_cases([], _Var, _CodeModel, CanFail, _StoreMap,
-		EndLabel, Code) -->
+		EndLabel, MaybeEnd, MaybeEnd, Code) -->
 	( { CanFail = can_fail } ->
 		code_info__generate_failure(FailCode)
 	;
@@ -306,8 +309,8 @@
 	{ Code = tree(FailCode, EndCode) }.
 
 switch_gen__generate_cases([case(_, _, Cons, Goal) | Cases], Var, CodeModel,
-		CanFail, StoreMap, EndLabel, CasesCode) -->
-	code_info__grab_code_info(CodeInfo0),
+		CanFail, StoreMap, EndLabel, MaybeEnd0, MaybeEnd, CasesCode) -->
+	code_info__remember_position(BranchStart),
 	(
 		{ Cases = [_|_] ; CanFail = can_fail }
 	->
@@ -315,7 +318,8 @@
 			NextLabel, TestCode),
 		trace__maybe_generate_internal_event_code(Goal, TraceCode),
 		code_gen__generate_goal(CodeModel, Goal, GoalCode),
-		code_info__generate_branch_end(CodeModel, StoreMap, SaveCode),
+		code_info__generate_branch_end(StoreMap, MaybeEnd0, MaybeEnd1,
+			SaveCode),
 		{ ElseCode = node([
 			goto(label(EndLabel)) -
 				"skip to the end of the switch",
@@ -328,25 +332,22 @@
 			tree(GoalCode,
 			tree(SaveCode,
 			     ElseCode))))
-		},
-		code_info__grab_code_info(CodeInfo1),
-		code_info__slap_code_info(CodeInfo0)
+		}
 	;
 		trace__maybe_generate_internal_event_code(Goal, TraceCode),
 		code_gen__generate_goal(CodeModel, Goal, GoalCode),
-		code_info__generate_branch_end(CodeModel, StoreMap, SaveCode),
+		code_info__generate_branch_end(StoreMap, MaybeEnd0, MaybeEnd1,
+			SaveCode),
 		{ ThisCaseCode =
 			tree(TraceCode,
 			tree(GoalCode,
 			     SaveCode))
-		},
-		code_info__grab_code_info(CodeInfo1),
-		code_info__slap_code_info(CodeInfo0)
+		}
 	),
+	code_info__reset_to_position(BranchStart),
 		% generate the rest of the cases.
 	switch_gen__generate_cases(Cases, Var, CodeModel, CanFail, StoreMap,
-		EndLabel, OtherCasesCode),
-	{ CasesCode = tree(ThisCaseCode, OtherCasesCode) },
-	code_info__slap_code_info(CodeInfo1).
+		EndLabel, MaybeEnd1, MaybeEnd, OtherCasesCode),
+	{ CasesCode = tree(ThisCaseCode, OtherCasesCode) }.
 
 %------------------------------------------------------------------------------%
Index: compiler/tag_switch.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/tag_switch.m,v
retrieving revision 1.44
diff -u -r1.44 tag_switch.m
--- tag_switch.m	1998/04/08 11:32:31	1.44
+++ tag_switch.m	1998/05/17 06:46:36
@@ -20,8 +20,10 @@
 	% Generate intelligent indexing code for tag based switches.
 
 :- pred tag_switch__generate(list(extended_case), var, code_model, can_fail,
-	store_map, label, code_tree, code_info, code_info).
-:- mode tag_switch__generate(in, in, in, in, in, in, out, in, out) is det.
+	store_map, label, branch_end, branch_end, code_tree,
+	code_info, code_info).
+:- mode tag_switch__generate(in, in, in, in, in, in, in, out, out, in, out)
+	is det.
 
 :- implementation.
 
@@ -176,7 +178,8 @@
 			;	jump_table
 			;	binary_search.
 
-tag_switch__generate(Cases, Var, CodeModel, CanFail, StoreMap, EndLabel, Code)
+tag_switch__generate(Cases, Var, CodeModel, CanFail, StoreMap, EndLabel,
+		MaybeEnd0, MaybeEnd, Code)
 		-->
 	% group the cases based on primary tag value
 	% and find out how many constructors share each primary tag value
@@ -274,19 +277,15 @@
 		tag_switch__generate_primary_binary_search(PtagCaseList,
 			0, MaxPrimary, PtagRval, VarRval, CodeModel, CanFail,
 			StoreMap, EndLabel, FailLabel, PtagCountMap,
-			no, MaybeFinalCodeInfo, CasesCode),
-		( { MaybeFinalCodeInfo = yes(FinalCodeInfo) } ->
-			code_info__slap_code_info(FinalCodeInfo)
-		;
-			{ error("binary search switch has no useful cases") }
-		)
+			no, MaybeEnd, CasesCode)
 	;
 		{ PrimaryMethod = jump_table },
 		{ tag_switch__order_ptags_by_value(0, MaxPrimary, PtagCaseMap,
 			PtagCaseList) },
 		tag_switch__generate_primary_jump_table(PtagCaseList,
 			0, MaxPrimary, VarRval, CodeModel, StoreMap,
-			EndLabel, FailLabel, PtagCountMap, Labels, TableCode),
+			EndLabel, FailLabel, PtagCountMap, MaybeEnd0, MaybeEnd,
+			Labels, TableCode),
 		{ SwitchCode = node([
 			computed_goto(PtagRval, Labels) -
 				"switch on primary tag"
@@ -307,14 +306,15 @@
 		tag_switch__generate_primary_try_chain(PtagCaseList,
 			PtagRval, VarRval, CodeModel, CanFail, StoreMap,
 			EndLabel, FailLabel, PtagCountMap, empty, empty,
-			CasesCode)
+			MaybeEnd0, MaybeEnd, CasesCode)
 	;
 		{ PrimaryMethod = try_me_else_chain },
 		{ tag_switch__order_ptags_by_count(PtagCountList, PtagCaseMap,
 			PtagCaseList) },
 		tag_switch__generate_primary_try_me_else_chain(PtagCaseList,
 			PtagRval, VarRval, CodeModel, CanFail, StoreMap,
-			EndLabel, FailLabel, PtagCountMap, CasesCode)
+			EndLabel, FailLabel, PtagCountMap, MaybeEnd0, MaybeEnd,
+			CasesCode)
 	),
 
 	{ Code =
@@ -322,7 +322,8 @@
 		tree(PtagCode,
 		tree(CasesCode,
 		tree(LabelledFailCode,
-		     EndCode)))) }.
+		     EndCode))))
+	}.
 
 %-----------------------------------------------------------------------------%
 
@@ -330,16 +331,18 @@
 
 :- pred tag_switch__generate_primary_try_me_else_chain(ptag_case_list,
 	rval, rval, code_model, can_fail, store_map, label, label,
-	ptag_count_map, code_tree, code_info, code_info).
+	ptag_count_map, branch_end, branch_end,
+	code_tree, code_info, code_info).
 :- mode tag_switch__generate_primary_try_me_else_chain(in, in, in, in, in, in,
-	in, in, in, out, in, out) is det.
+	in, in, in, in, out, out, in, out) is det.
 
-tag_switch__generate_primary_try_me_else_chain([], _, _, _, _, _, _, _, _, _)
-		-->
+tag_switch__generate_primary_try_me_else_chain([], _, _, _, _, _, _, _, _, _,
+		_, _) -->
 	{ error("generate_primary_try_me_else_chain: empty switch") }.
 tag_switch__generate_primary_try_me_else_chain([PtagGroup | PtagGroups],
 		TagRval, VarRval, CodeModel, CanFail, StoreMap,
-		EndLabel, FailLabel, PtagCountMap, Code) -->
+		EndLabel, FailLabel, PtagCountMap, MaybeEnd0, MaybeEnd, Code)
+		-->
 	{ PtagGroup = Primary - (StagLoc - StagGoalMap) },
 	{ map__lookup(PtagCountMap, Primary, CountInfo) },
 	{ CountInfo = StagLoc1 - MaxSecondary },
@@ -351,7 +354,7 @@
 	(
 		{ PtagGroups = [_|_] ; CanFail = can_fail }
 	->
-		code_info__grab_code_info(CodeInfo),
+		code_info__remember_position(BranchStart),
 		code_info__get_next_label(ElseLabel),
 		{ TestRval = binop(ne, TagRval,
 			unop(mktag, const(int_const(Primary)))) },
@@ -361,7 +364,8 @@
 		]) },
 		tag_switch__generate_primary_tag_code(StagGoalMap,
 			Primary, MaxSecondary, StagLoc, VarRval, CodeModel,
-			StoreMap, EndLabel, FailLabel, TagCode),
+			StoreMap, EndLabel, FailLabel, MaybeEnd0, MaybeEnd1,
+			TagCode),
 		{ ElseCode = node([
 			label(ElseLabel) -
 				"handle next primary tag"
@@ -372,11 +376,12 @@
 			     ElseCode))
 		},
 		( { PtagGroups = [_|_] } ->
-			code_info__slap_code_info(CodeInfo),
+			code_info__reset_to_position(BranchStart),
 			tag_switch__generate_primary_try_me_else_chain(
 				PtagGroups, TagRval, VarRval, CodeModel,
 				CanFail, StoreMap, EndLabel, FailLabel,
-				PtagCountMap, OtherTagsCode),
+				PtagCountMap, MaybeEnd1, MaybeEnd,
+				OtherTagsCode),
 			{ Code = tree(ThisTagCode, OtherTagsCode) }
 		;
 			% FailLabel ought to be the next label anyway,
@@ -386,13 +391,14 @@
 				goto(label(FailLabel)) -
 					"primary tag with no code to handle it"
 			]) },
+			{ MaybeEnd = MaybeEnd1 },
 			{ Code = tree(ThisTagCode, FailCode) }
 		)
 	;
 		tag_switch__generate_primary_tag_code(StagGoalMap,
 			Primary, MaxSecondary, StagLoc, VarRval, CodeModel,
-			StoreMap, EndLabel, FailLabel, ThisTagCode),
-		{ Code = ThisTagCode }
+			StoreMap, EndLabel, FailLabel, MaybeEnd0, MaybeEnd,
+			Code)
 	).
 
 %-----------------------------------------------------------------------------%
@@ -401,15 +407,18 @@
 
 :- pred tag_switch__generate_primary_try_chain(ptag_case_list,
 	rval, rval, code_model, can_fail, store_map, label, label,
-	ptag_count_map, code_tree, code_tree, code_tree, code_info, code_info).
+	ptag_count_map, code_tree, code_tree, branch_end, branch_end,
+	code_tree, code_info, code_info).
 :- mode tag_switch__generate_primary_try_chain(in, in, in, in, in, in,
-	in, in, in, in, in, out, in, out) is det.
+	in, in, in, in, in, in, out, out, in, out) is det.
 
-tag_switch__generate_primary_try_chain([], _, _, _, _, _, _, _, _, _, _, _) -->
+tag_switch__generate_primary_try_chain([], _, _, _, _, _, _, _, _, _, _, _,
+		_, _) -->
 	 { error("empty list in generate_primary_try_chain") }.
 tag_switch__generate_primary_try_chain([PtagGroup | PtagGroups],
 		TagRval, VarRval, CodeModel, CanFail, StoreMap, EndLabel,
-		FailLabel, PtagCountMap, PrevTests0, PrevCases0, Code) -->
+		FailLabel, PtagCountMap, PrevTests0, PrevCases0,
+		MaybeEnd0, MaybeEnd, Code) -->
 	{ PtagGroup = Primary - (StagLoc - StagGoalMap) },
 	{ map__lookup(PtagCountMap, Primary, CountInfo) },
 	{ CountInfo = StagLoc1 - MaxSecondary },
@@ -421,7 +430,7 @@
 	(
 		{ PtagGroups = [_|_] ; CanFail = can_fail }
 	->
-		code_info__grab_code_info(CodeInfo),
+		code_info__remember_position(BranchStart),
 		code_info__get_next_label(ThisPtagLabel),
 		{ TestRval = binop(eq, TagRval,
 			unop(mktag, const(int_const(Primary)))) },
@@ -435,20 +444,23 @@
 		]) },
 		tag_switch__generate_primary_tag_code(StagGoalMap,
 			Primary, MaxSecondary, StagLoc, VarRval, CodeModel,
-			StoreMap, EndLabel, FailLabel, TagCode),
+			StoreMap, EndLabel, FailLabel, MaybeEnd0, MaybeEnd1,
+			TagCode),
 		{ PrevTests = tree(PrevTests0, TestCode) },
 		{ PrevCases = tree(tree(LabelCode, TagCode), PrevCases0) },
 		( { PtagGroups = [_|_] } ->
-			code_info__slap_code_info(CodeInfo),
+			code_info__reset_to_position(BranchStart),
 			tag_switch__generate_primary_try_chain(PtagGroups,
 				TagRval, VarRval, CodeModel, CanFail, StoreMap,
 				EndLabel, FailLabel, PtagCountMap,
-				PrevTests, PrevCases, Code)
+				PrevTests, PrevCases, MaybeEnd1, MaybeEnd,
+				Code)
 		;
 			{ FailCode = node([
 				goto(label(FailLabel)) -
 					"primary tag with no code to handle it"
 			]) },
+			{ MaybeEnd = MaybeEnd1 },
 			{ Code = tree(PrevTests, tree(FailCode, PrevCases)) }
 		)
 	;
@@ -458,7 +470,7 @@
 		tag_switch__generate_primary_tag_code(StagGoalMap,
 			Primary, MaxSecondary, StagLoc, VarRval,
 			CodeModel, StoreMap, EndLabel, FailLabel,
-			TagCode),
+			MaybeEnd0, MaybeEnd, TagCode),
 		{ Code =
 			tree(PrevTests0,
 			tree(Comment,
@@ -474,19 +486,20 @@
 
 :- pred tag_switch__generate_primary_jump_table(ptag_case_list, int, int,
 	rval, code_model, store_map, label, label, ptag_count_map,
-	list(label), code_tree, code_info, code_info).
+	branch_end, branch_end, list(label), code_tree, code_info, code_info).
 :- mode tag_switch__generate_primary_jump_table(in, in, in, in,
-	in, in, in, in, in, out, out, in, out) is det.
+	in, in, in, in, in, in, out, out, out, in, out) is det.
 
 tag_switch__generate_primary_jump_table(PtagGroups, CurPrimary, MaxPrimary,
 		VarRval, CodeModel, StoreMap, EndLabel, FailLabel, PtagCountMap,
-		Labels, Code) -->
+		MaybeEnd0, MaybeEnd, Labels, Code) -->
 	( { CurPrimary > MaxPrimary } ->
 		{ PtagGroups = [] ->
 			true
 		;
 			error("caselist not empty when reaching limiting primary tag")
 		},
+		{ MaybeEnd = MaybeEnd0 },
 		{ Labels = [] },
 		{ Code = empty }
 	;
@@ -510,20 +523,20 @@
 					StagGoalMap, CurPrimary, MaxSecondary,
 					StagLoc, VarRval, CodeModel,
 					StoreMap, EndLabel, FailLabel,
-					ThisTagCode)
+					MaybeEnd0, MaybeEnd1, ThisTagCode)
 			;
-				code_info__grab_code_info(CodeInfo),
+				code_info__remember_position(BranchStart),
 				tag_switch__generate_primary_tag_code(
 					StagGoalMap, CurPrimary, MaxSecondary,
 					StagLoc, VarRval, CodeModel,
 					StoreMap, EndLabel, FailLabel,
-					ThisTagCode),
-				code_info__slap_code_info(CodeInfo)
+					MaybeEnd0, MaybeEnd1, ThisTagCode),
+				code_info__reset_to_position(BranchStart)
 			),
 			tag_switch__generate_primary_jump_table(PtagGroups1,
 				NextPrimary, MaxPrimary, VarRval, CodeModel,
 				StoreMap, EndLabel, FailLabel, PtagCountMap,
-				OtherLabels, OtherCode),
+				MaybeEnd1, MaybeEnd, OtherLabels, OtherCode),
 			{ Labels = [NewLabel | OtherLabels] },
 			{ Code =
 				tree(LabelCode,
@@ -534,7 +547,7 @@
 			tag_switch__generate_primary_jump_table(PtagGroups,
 				NextPrimary, MaxPrimary, VarRval, CodeModel,
 				StoreMap, EndLabel, FailLabel, PtagCountMap,
-				OtherLabels, Code),
+				MaybeEnd0, MaybeEnd, OtherLabels, Code),
 			{ Labels = [FailLabel | OtherLabels] }
 		)
 	).
@@ -547,15 +560,15 @@
 
 :- pred tag_switch__generate_primary_binary_search(ptag_case_list, int, int,
 	rval, rval, code_model, can_fail, store_map, label, label,
-	ptag_count_map, maybe(code_info), maybe(code_info),
-	code_tree, code_info, code_info).
+	ptag_count_map, branch_end, branch_end, code_tree,
+	code_info, code_info).
 :- mode tag_switch__generate_primary_binary_search(in, in, in,
 	in, in, in, in, in, in, in, in, in, out, out, in, out) is det.
 
 tag_switch__generate_primary_binary_search(PtagGroups, MinPtag, MaxPtag,
 		PtagRval, VarRval, CodeModel, CanFail, StoreMap,
 		EndLabel, FailLabel, PtagCountMap,
-		MaybeFinalCodeInfo0, MaybeFinalCodeInfo, Code) -->
+		MaybeEnd0, MaybeEnd, Code) -->
 	( { MinPtag = MaxPtag } ->
 		{ CurPrimary = MinPtag },
 		( { PtagGroups = [] } ->
@@ -573,7 +586,7 @@
 				{ CanFail = cannot_fail },
 				{ Code = empty }
 			),
-			{ MaybeFinalCodeInfo = MaybeFinalCodeInfo0 }
+			{ MaybeEnd = MaybeEnd0 }
 		; { PtagGroups = [CurPrimary - PrimaryInfo] } ->
 			{ PrimaryInfo = StagLoc - StagGoalMap },
 			{ map__lookup(PtagCountMap, CurPrimary, CountInfo) },
@@ -584,11 +597,9 @@
 				error("secondary tag locations differ in generate_primary_jump_table")
 			},
 			tag_switch__generate_primary_tag_code(
-				StagGoalMap, CurPrimary, MaxSecondary,
-				StagLoc, VarRval, CodeModel,
-				StoreMap, EndLabel, FailLabel, Code),
-			code_info__grab_code_info(CodeInfo),
-			{ MaybeFinalCodeInfo = yes(CodeInfo) }
+				StagGoalMap, CurPrimary, MaxSecondary, StagLoc,
+				VarRval, CodeModel, StoreMap, EndLabel,
+				FailLabel, MaybeEnd0, MaybeEnd, Code)
 		;
 			{ error("caselist not singleton or empty when binary search ends") }
 		)
@@ -620,16 +631,16 @@
 				LabelComment
 		]) },
 
-		code_info__grab_code_info(CodeInfo),
+		code_info__remember_position(BranchStart),
 		tag_switch__generate_primary_binary_search(LowGroups,
 			MinPtag, LowRangeEnd, PtagRval, VarRval, CodeModel,
 			CanFail, StoreMap, EndLabel, FailLabel, PtagCountMap,
-			MaybeFinalCodeInfo0, MaybeFinalCodeInfo1, LowRangeCode),
-		code_info__slap_code_info(CodeInfo),
+			MaybeEnd0, MaybeEnd1, LowRangeCode),
+		code_info__reset_to_position(BranchStart),
 		tag_switch__generate_primary_binary_search(HighGroups,
 			HighRangeStart, MaxPtag, PtagRval, VarRval, CodeModel,
 			CanFail, StoreMap, EndLabel, FailLabel, PtagCountMap,
-			MaybeFinalCodeInfo1, MaybeFinalCodeInfo, HighRangeCode),
+			MaybeEnd1, MaybeEnd, HighRangeCode),
 
 		{ Code =
 			tree(IfCode,
@@ -646,13 +657,14 @@
 	% use a jump table to implement the secondary switch.
 
 :- pred tag_switch__generate_primary_tag_code(stag_goal_map, tag_bits, int,
-	stag_loc, rval, code_model, store_map,
-	label, label, code_tree, code_info, code_info).
+	stag_loc, rval, code_model, store_map, label, label,
+	branch_end, branch_end, code_tree, code_info, code_info).
 :- mode tag_switch__generate_primary_tag_code(in, in, in, in, in, in, in,
-	in, in, out, in, out) is det.
+	in, in, in, out, out, in, out) is det.
 
 tag_switch__generate_primary_tag_code(GoalMap, Primary, MaxSecondary, StagLoc,
-		Rval, CodeModel, StoreMap, EndLabel, FailLabel, Code) -->
+		Rval, CodeModel, StoreMap, EndLabel, FailLabel,
+		MaybeEnd0, MaybeEnd, Code) -->
 	{ map__to_assoc_list(GoalMap, GoalList) },
 	(
 		{ StagLoc = none }
@@ -662,8 +674,8 @@
 			trace__maybe_generate_internal_event_code(Goal,
 				TraceCode),
 			code_gen__generate_goal(CodeModel, Goal, GoalCode),
-			code_info__generate_branch_end(CodeModel, StoreMap,
-				SaveCode),
+			code_info__generate_branch_end(StoreMap,
+				MaybeEnd0, MaybeEnd, SaveCode),
 			{ GotoCode = node([
 				goto(label(EndLabel)) -
 					"skip to end of primary tag switch"
@@ -749,7 +761,8 @@
 			{ SecondaryMethod = jump_table },
 			tag_switch__generate_secondary_jump_table(GoalList,
 				0, MaxSecondary, CodeModel, StoreMap,
-				EndLabel, FailLabel, Labels, CasesCode),
+				EndLabel, FailLabel, MaybeEnd0, MaybeEnd,
+				Labels, CasesCode),
 			{ SwitchCode = node([
 				computed_goto(StagRval, Labels) -
 					"switch on secondary tag"
@@ -760,23 +773,20 @@
 			tag_switch__generate_secondary_binary_search(GoalList,
 				0, MaxSecondary, StagRval, CodeModel, CanFail,
 				StoreMap, EndLabel, FailLabel,
-				no, MaybeFinalCodeInfo, Code),
-			( { MaybeFinalCodeInfo = yes(FinalCodeInfo) } ->
-				code_info__slap_code_info(FinalCodeInfo)
-			;
-				{ error("binary search switch has no useful cases") }
-			)
+				MaybeEnd0, MaybeEnd, Code)
 		;
 			{ SecondaryMethod = try_chain },
 			tag_switch__generate_secondary_try_chain(GoalList,
 				StagRval, CodeModel, CanFail, StoreMap,
-				EndLabel, FailLabel, empty, empty, Codes),
+				EndLabel, FailLabel, empty, empty,
+				MaybeEnd0, MaybeEnd, Codes),
 			{ Code = tree(StagCode, Codes) }
 		;
 			{ SecondaryMethod = try_me_else_chain },
 			tag_switch__generate_secondary_try_me_else_chain(
 				GoalList, StagRval, CodeModel, CanFail,
-				StoreMap, EndLabel, FailLabel, Codes),
+				StoreMap, EndLabel, FailLabel,
+				MaybeEnd0, MaybeEnd, Codes),
 			{ Code = tree(StagCode, Codes) }
 		)
 	).
@@ -787,17 +797,19 @@
 
 :- pred tag_switch__generate_secondary_try_me_else_chain(stag_goal_list, rval,
 	code_model, can_fail, store_map, label, label,
-	code_tree, code_info, code_info).
+	branch_end, branch_end, code_tree, code_info, code_info).
 :- mode tag_switch__generate_secondary_try_me_else_chain(in, in, in, in, in,
-	in, in, out, in, out) is det.
+	in, in, in, out, out, in, out) is det.
 
-tag_switch__generate_secondary_try_me_else_chain([], _, _, _, _, _, _, _) -->
+tag_switch__generate_secondary_try_me_else_chain([], _, _, _, _, _, _, _, _, _)
+		-->
 	{ error("generate_secondary_try_me_else_chain: empty switch") }.
 tag_switch__generate_secondary_try_me_else_chain([Case0 | Cases0], StagRval,
-		CodeModel, CanFail, StoreMap, EndLabel, FailLabel, Code) -->
+		CodeModel, CanFail, StoreMap, EndLabel, FailLabel,
+		MaybeEnd0, MaybeEnd, Code) -->
 	{ Case0 = Secondary - Goal },
 	( { Cases0 = [_|_] ; CanFail = can_fail } ->
-		code_info__grab_code_info(CodeInfo),
+		code_info__remember_position(BranchStart),
 		code_info__get_next_label(ElseLabel),
 		{ TestCode = node([
 			if_val(binop(ne, StagRval,
@@ -807,7 +819,8 @@
 		]) },
 		trace__maybe_generate_internal_event_code(Goal, TraceCode),
 		code_gen__generate_goal(CodeModel, Goal, GoalCode),
-		code_info__generate_branch_end(CodeModel, StoreMap, SaveCode),
+		code_info__generate_branch_end(StoreMap, MaybeEnd0, MaybeEnd1,
+			SaveCode),
 		{ GotoLabelCode = node([
 			goto(label(EndLabel)) -
 				"skip to end of secondary tag switch",
@@ -822,22 +835,25 @@
 			     GotoLabelCode))))
 		},
 		( { Cases0 = [_|_] } ->
-			code_info__slap_code_info(CodeInfo),
+			code_info__reset_to_position(BranchStart),
 			tag_switch__generate_secondary_try_me_else_chain(Cases0,
 				StagRval, CodeModel, CanFail, StoreMap,
-				EndLabel, FailLabel, OtherCode),
+				EndLabel, FailLabel, MaybeEnd1, MaybeEnd,
+				OtherCode),
 			{ Code = tree(ThisCode, OtherCode) }
 		;
 			{ FailCode = node([
 				goto(label(FailLabel)) -
 					"secondary tag does not match"
 			]) },
+			{ MaybeEnd = MaybeEnd1 },
 			{ Code = tree(ThisCode, FailCode) }
 		)
 	;
 		trace__maybe_generate_internal_event_code(Goal, TraceCode),
 		code_gen__generate_goal(CodeModel, Goal, GoalCode),
-		code_info__generate_branch_end(CodeModel, StoreMap, SaveCode),
+		code_info__generate_branch_end(StoreMap, MaybeEnd0, MaybeEnd,
+			SaveCode),
 		{ GotoCode = node([
 			goto(label(EndLabel)) -
 				"skip to end of secondary tag switch"
@@ -855,19 +871,20 @@
 	% Generate a switch on a secondary tag value using a try chain.
 
 :- pred tag_switch__generate_secondary_try_chain(stag_goal_list, rval,
-	code_model, can_fail, store_map, label, label,
-	code_tree, code_tree, code_tree, code_info, code_info).
+	code_model, can_fail, store_map, label, label, code_tree, code_tree,
+	branch_end, branch_end, code_tree, code_info, code_info).
 :- mode tag_switch__generate_secondary_try_chain(in, in, in, in, in,
-	in, in, in, in, out, in, out) is det.
+	in, in, in, in, in, out, out, in, out) is det.
 
-tag_switch__generate_secondary_try_chain([], _, _, _, _, _, _, _, _, _) -->
+tag_switch__generate_secondary_try_chain([], _, _, _, _, _, _, _, _, _, _, _)
+		-->
 	{ error("generate_secondary_try_chain: empty switch") }.
 tag_switch__generate_secondary_try_chain([Case0 | Cases0], StagRval,
 		CodeModel, CanFail, StoreMap, EndLabel, FailLabel,
-		PrevTests0, PrevCases0, Code) -->
+		PrevTests0, PrevCases0, MaybeEnd0, MaybeEnd, Code) -->
 	{ Case0 = Secondary - Goal },
 	( { Cases0 = [_|_] ; CanFail = can_fail } ->
-		code_info__grab_code_info(CodeInfo),
+		code_info__remember_position(BranchStart),
 		code_info__get_next_label(ThisStagLabel),
 		{ TestCode = node([
 			if_val(binop(eq, StagRval,
@@ -881,7 +898,8 @@
 		]) },
 		trace__maybe_generate_internal_event_code(Goal, TraceCode),
 		code_gen__generate_goal(CodeModel, Goal, GoalCode),
-		code_info__generate_branch_end(CodeModel, StoreMap, SaveCode),
+		code_info__generate_branch_end(StoreMap, MaybeEnd0, MaybeEnd1,
+			SaveCode),
 		{ GotoCode = node([
 			goto(label(EndLabel)) -
 				"skip to end of secondary tag switch"
@@ -896,22 +914,24 @@
 		{ PrevTests = tree(PrevTests0, TestCode) },
 		{ PrevCases = tree(ThisCode, PrevCases0) },
 		( { Cases0 = [_|_] } ->
-			code_info__slap_code_info(CodeInfo),
+			code_info__reset_to_position(BranchStart),
 			tag_switch__generate_secondary_try_chain(Cases0,
 				StagRval, CodeModel, CanFail, StoreMap,
-				EndLabel, FailLabel,
-				PrevTests, PrevCases, Code)
+				EndLabel, FailLabel, PrevTests, PrevCases,
+				MaybeEnd1, MaybeEnd, Code)
 		;
 			{ FailCode = node([
 				goto(label(FailLabel)) -
 					"secondary tag with no code to handle it"
 			]) },
+			{ MaybeEnd = MaybeEnd1 },
 			{ Code = tree(PrevTests, tree(FailCode, PrevCases)) }
 		)
 	;
 		trace__maybe_generate_internal_event_code(Goal, TraceCode),
 		code_gen__generate_goal(CodeModel, Goal, GoalCode),
-		code_info__generate_branch_end(CodeModel, StoreMap, SaveCode),
+		code_info__generate_branch_end(StoreMap, MaybeEnd0, MaybeEnd,
+			SaveCode),
 		{ GotoCode = node([
 			goto(label(EndLabel)) -
 				"skip to end of secondary tag switch"
@@ -932,19 +952,21 @@
 	% that has an entry for all possible secondary tag values.
 
 :- pred tag_switch__generate_secondary_jump_table(stag_goal_list, int, int,
-	code_model, store_map, label, label, list(label),
-	code_tree, code_info, code_info).
+	code_model, store_map, label, label, branch_end, branch_end,
+	list(label), code_tree, code_info, code_info).
 :- mode tag_switch__generate_secondary_jump_table(in, in, in, in,
-	in, in, in, out, out, in, out) is det.
+	in, in, in, in, out, out, out, in, out) is det.
 
 tag_switch__generate_secondary_jump_table(CaseList, CurSecondary, MaxSecondary,
-		CodeModel, StoreMap, EndLabel, FailLabel, Labels, Code) -->
+		CodeModel, StoreMap, EndLabel, FailLabel, MaybeEnd0, MaybeEnd,
+		Labels, Code) -->
 	( { CurSecondary > MaxSecondary } ->
 		{ CaseList = [] ->
 			true
 		;
 			error("caselist not empty when reaching limiting secondary tag")
 		},
+		{ MaybeEnd = MaybeEnd0 },
 		{ Labels = [] },
 		{ Code = empty }
 	;
@@ -955,16 +977,16 @@
 				label(NewLabel) -
 					"start of case in secondary tag switch"
 			]) },
-			code_info__grab_code_info(CodeInfo),
+			code_info__remember_position(BranchStart),
 			trace__maybe_generate_internal_event_code(Goal,
 				TraceCode),
 			code_gen__generate_goal(CodeModel, Goal, GoalCode),
-			code_info__generate_branch_end(CodeModel, StoreMap,
-				SaveCode),
+			code_info__generate_branch_end(StoreMap,
+				MaybeEnd0, MaybeEnd1, SaveCode),
 			( { CaseList1 = [] } ->
 				[]
 			;
-				code_info__slap_code_info(CodeInfo)
+				code_info__reset_to_position(BranchStart)
 			),
 			{ GotoCode = node([
 				goto(label(EndLabel)) -
@@ -972,8 +994,8 @@
 			]) },
 			tag_switch__generate_secondary_jump_table(CaseList1,
 				NextSecondary, MaxSecondary, CodeModel,
-				StoreMap, EndLabel, FailLabel, OtherLabels,
-				OtherCode),
+				StoreMap, EndLabel, FailLabel,
+				MaybeEnd1, MaybeEnd, OtherLabels, OtherCode),
 			{ Labels = [NewLabel | OtherLabels] },
 			{ Code =
 				tree(LabelCode,
@@ -986,8 +1008,8 @@
 		;
 			tag_switch__generate_secondary_jump_table(CaseList,
 				NextSecondary, MaxSecondary, CodeModel,
-				StoreMap, EndLabel, FailLabel, OtherLabels,
-				Code),
+				StoreMap, EndLabel, FailLabel,
+				MaybeEnd0, MaybeEnd, OtherLabels, Code),
 			{ Labels = [FailLabel | OtherLabels] }
 		)
 	).
@@ -1000,14 +1022,13 @@
 
 :- pred tag_switch__generate_secondary_binary_search(stag_goal_list, int, int,
 	rval, code_model, can_fail, store_map, label, label,
-	maybe(code_info), maybe(code_info),
-	code_tree, code_info, code_info).
+	branch_end, branch_end, code_tree, code_info, code_info).
 :- mode tag_switch__generate_secondary_binary_search(in, in, in,
 	in, in, in, in, in, in, in, out, out, in, out) is det.
 
 tag_switch__generate_secondary_binary_search(StagGoals, MinStag, MaxStag,
 		StagRval, CodeModel, CanFail, StoreMap, EndLabel, FailLabel,
-		MaybeFinalCodeInfo0, MaybeFinalCodeInfo, Code) -->
+		MaybeEnd0, MaybeEnd, Code) -->
 	( { MinStag = MaxStag } ->
 		{ CurSec = MinStag },
 		( { StagGoals = [] } ->
@@ -1025,20 +1046,18 @@
 				{ CanFail = cannot_fail },
 				{ Code = empty }
 			),
-			{ MaybeFinalCodeInfo = MaybeFinalCodeInfo0 }
+			{ MaybeEnd = MaybeEnd0 }
 		; { StagGoals = [CurSec - Goal] } ->
 			trace__maybe_generate_internal_event_code(Goal,
 				TraceCode),
 			code_gen__generate_goal(CodeModel, Goal, GoalCode),
-			code_info__generate_branch_end(CodeModel, StoreMap,
-				SaveCode),
+			code_info__generate_branch_end(StoreMap,
+				MaybeEnd0, MaybeEnd, SaveCode),
 			{ Code =
 				tree(TraceCode,
 				tree(GoalCode,
 				     SaveCode))
-			},
-			code_info__grab_code_info(CodeInfo),
-			{ MaybeFinalCodeInfo = yes(CodeInfo) }
+			}
 		;
 			{ error("goallist not singleton or empty when binary search ends") }
 		)
@@ -1070,16 +1089,16 @@
 				LabelComment
 		]) },
 
-		code_info__grab_code_info(CodeInfo),
+		code_info__remember_position(BranchStart),
 		tag_switch__generate_secondary_binary_search(LowGoals,
 			MinStag, LowRangeEnd, StagRval, CodeModel,
 			CanFail, StoreMap, EndLabel, FailLabel,
-			MaybeFinalCodeInfo0, MaybeFinalCodeInfo1, LowRangeCode),
-		code_info__slap_code_info(CodeInfo),
+			MaybeEnd0, MaybeEnd1, LowRangeCode),
+		code_info__reset_to_position(BranchStart),
 		tag_switch__generate_secondary_binary_search(HighGoals,
 			HighRangeStart, MaxStag, StagRval, CodeModel,
 			CanFail, StoreMap, EndLabel, FailLabel,
-			MaybeFinalCodeInfo1, MaybeFinalCodeInfo, HighRangeCode),
+			MaybeEnd1, MaybeEnd, HighRangeCode),
 
 		{ Code =
 			tree(IfCode,
Index: compiler/trace.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/trace.m,v
retrieving revision 1.10
diff -u -r1.10 trace.m
--- trace.m	1998/06/18 06:06:58	1.10
+++ trace.m	1998/06/18 06:10:39
@@ -68,16 +68,21 @@
 	% layouts).
 :- pred trace__fail_vars(module_info::in, proc_info::in, set(var)::out) is det.
 
-	% Set up the code generator state for tracing, by reserving stack slots
-	% for the call number, call depth and (for interface tracing) for
-	% the flag that says whether this call should be traced.
-:- pred trace__setup(trace_level::in, code_info::in, code_info::out) is det.
+	% Reserve the stack slots for the call number, call depth and
+	% (for interface tracing) for the flag that says whether this call
+	% should be traced. Return our (abstract) struct that says which
+	% slots these are, so that it can be made part of the code generator
+	% state.
+:- pred trace__setup(trace_level::in, trace_info::out,
+	code_info::in, code_info::out) is det.
 
 	% Generate code to fill in the reserevd stack slots.
 :- pred trace__generate_slot_fill_code(trace_info::in, code_tree::out) is det.
 
-	% Generate code to prepare for a call.
-:- pred trace__prepare_for_call(trace_info::in, code_tree::out) is det.
+	% If we are doing execution tracing, generate code to prepare for
+	% a call.
+:- pred trace__prepare_for_call(code_tree::out, code_info::in, code_info::out)
+	is det.
 
 	% If we are doing execution tracing, generate code for an internal
 	% trace event. This predicate must be called just before generating
@@ -159,7 +164,7 @@
 		error("length mismatch in trace__fail_vars")
 	).
 
-trace__setup(TraceLevel) -->
+trace__setup(TraceLevel, TraceInfo) -->
 	code_info__get_trace_slot(CallNumSlot),
 	code_info__get_trace_slot(CallDepthSlot),
 	( { trace_level_trace_ports(TraceLevel, yes) } ->
@@ -168,8 +173,7 @@
 		code_info__get_trace_slot(CallFromFullSlot),
 		{ TraceType = interface_trace(CallFromFullSlot) }
 	),
-	{ TraceInfo = trace_info(CallNumSlot, CallDepthSlot, TraceType) },
-	code_info__set_maybe_trace_info(yes(TraceInfo)).
+	{ TraceInfo = trace_info(CallNumSlot, CallDepthSlot, TraceType) }.
 
 trace__generate_slot_fill_code(TraceInfo, TraceCode) :-
 	TraceInfo = trace_info(CallNumLval, CallDepthLval, TraceType),
@@ -198,24 +202,32 @@
 			will_not_call_mercury, no, yes) - ""
 	]).
 
-trace__prepare_for_call(TraceInfo, TraceCode) :-
-	TraceInfo = trace_info(_CallNumLval, CallDepthLval, TraceType),
-	trace__stackref_to_string(CallDepthLval, CallDepthStr),
-	string__append_list(["MR_trace_reset_depth(", CallDepthStr, ");\n"],
-		ResetDepthStmt),
-	(
-		TraceType = interface_trace(_),
-		TraceCode = node([
-			c_code("MR_trace_from_full = FALSE;\n") - "",
-			c_code(ResetDepthStmt) - ""
-		])
+trace__prepare_for_call(TraceCode) -->
+	code_info__get_maybe_trace_info(MaybeTraceInfo),
+	{
+		MaybeTraceInfo = yes(TraceInfo)
+	->
+		TraceInfo = trace_info(_CallNumLval, CallDepthLval, TraceType),
+		trace__stackref_to_string(CallDepthLval, CallDepthStr),
+		string__append_list(["MR_trace_reset_depth(", CallDepthStr,
+			");\n"],
+			ResetDepthStmt),
+		(
+			TraceType = interface_trace(_),
+			TraceCode = node([
+				c_code("MR_trace_from_full = FALSE;\n") - "",
+				c_code(ResetDepthStmt) - ""
+			])
+		;
+			TraceType = full_trace,
+			TraceCode = node([
+				c_code("MR_trace_from_full = TRUE;\n") - "",
+				c_code(ResetDepthStmt) - ""
+			])
+		)
 	;
-		TraceType = full_trace,
-		TraceCode = node([
-			c_code("MR_trace_from_full = TRUE;\n") - "",
-			c_code(ResetDepthStmt) - ""
-		])
-	).
+		TraceCode = empty
+	}.
 
 trace__maybe_generate_internal_event_code(Goal, Code) -->
 	code_info__get_maybe_trace_info(MaybeTraceInfo),
Index: compiler/unify_gen.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/unify_gen.m,v
retrieving revision 1.90
diff -u -r1.90 unify_gen.m
--- unify_gen.m	1998/03/03 17:36:27	1.90
+++ unify_gen.m	1998/05/17 07:08:19
@@ -13,68 +13,85 @@
 % eventually generate the out-of-line code (unify_proc.m).
 %
 %---------------------------------------------------------------------------%
-%---------------------------------------------------------------------------%
 
 :- module unify_gen.
 
 :- interface.
 
 :- import_module hlds_goal, hlds_data, llds, code_info.
-:- import_module list, term.
+:- import_module term.
 
-:- type test_sense --->
-		branch_on_success
+:- type test_sense
+	--->	branch_on_success
 	;	branch_on_failure.
 
-	% Generate code for an assignment unification.
-	% (currently implemented as a cached assignment).
-:- pred unify_gen__generate_assignment(var, var, code_tree,
+:- pred unify_gen__generate_unification(code_model, unification, code_tree,
 	code_info, code_info).
-:- mode unify_gen__generate_assignment(in, in, out, in, out) is det.
-
-	% Generate a construction unification
-:- pred unify_gen__generate_construction(var, cons_id,
-	list(var), list(uni_mode), code_tree, code_info, code_info).
-:- mode unify_gen__generate_construction(in, in, in, in, out, in, out) is det.
-
-:- pred unify_gen__generate_det_deconstruction(var, cons_id,
-	list(var), list(uni_mode), code_tree, code_info, code_info).
-:- mode unify_gen__generate_det_deconstruction(in, in, in, in, out,
-	in, out) is det.
-
-:- pred unify_gen__generate_semi_deconstruction(var, cons_id,
-	list(var), list(uni_mode), code_tree, code_info, code_info).
-:- mode unify_gen__generate_semi_deconstruction(in, in, in, in, out, in, out)
-	is det.
-
-:- pred unify_gen__generate_test(var, var, code_tree, code_info, code_info).
-:- mode unify_gen__generate_test(in, in, out, in, out) is det.
+:- mode unify_gen__generate_unification(in, in, out, in, out) is det.
 
 :- pred unify_gen__generate_tag_test(var, cons_id, test_sense, label,
 	code_tree, code_info, code_info).
 :- mode unify_gen__generate_tag_test(in, in, in, out, out, in, out) is det.
 
-:- pred unify_gen__generate_tag_rval(var, cons_id, rval, code_tree,
-	code_info, code_info).
-:- mode unify_gen__generate_tag_rval(in, in, out, out, in, out) is det.
-
 %---------------------------------------------------------------------------%
 
 :- implementation.
 
 :- import_module hlds_module, hlds_pred, prog_data, prog_out, code_util.
 :- import_module mode_util, type_util, code_aux, hlds_out, tree, arg_info.
-:- import_module bool, string, int, map, require, std_util.
+:- import_module bool, string, int, list, map, require, std_util.
 
 :- type uni_val		--->	ref(var)
 			;	lval(lval).
 
 %---------------------------------------------------------------------------%
 
+unify_gen__generate_unification(CodeModel, Uni, Code) -->
+	{ CodeModel = model_non ->
+		error("nondet unification in unify_gen__generate_unification")
+	;
+		true
+	},
+	(
+		{ Uni = assign(Left, Right) },
+		unify_gen__generate_assignment(Left, Right, Code)
+	;
+		{ Uni = construct(Var, ConsId, Args, Modes) },
+		unify_gen__generate_construction(Var, ConsId,
+			Args, Modes, Code)
+	;
+		{ Uni = deconstruct(Var, ConsId, Args, Modes, _Det) },
+		( { CodeModel = model_det } ->
+			unify_gen__generate_det_deconstruction(Var, ConsId,
+				Args, Modes, Code)
+		;
+			unify_gen__generate_semi_deconstruction(Var, ConsId,
+				Args, Modes, Code)
+		)
+	;
+		{ Uni = simple_test(Var1, Var2) },
+		( { CodeModel = model_det } ->
+			{ error("det simple_test during code generation") }
+		;
+			unify_gen__generate_test(Var1, Var2, Code)
+		)
+	;
+			% These should have been transformed into calls
+			% to unification procedures by polymorphism.m.
+		{ Uni = complicated_unify(_UniMode, _CanFail) },
+		{ error("complicated unify during code generation") }
+	).
+
+%---------------------------------------------------------------------------%
+
 	% assignment unifications are generated by simply caching the
 	% bound variable as the expression that generates the free
 	% variable. No immediate code is generated.
 
+:- pred unify_gen__generate_assignment(var, var, code_tree,
+	code_info, code_info).
+:- mode unify_gen__generate_assignment(in, in, out, in, out) is det.
+
 unify_gen__generate_assignment(VarA, VarB, empty) -->
 	(
 		code_info__variable_is_forward_live(VarA)
@@ -95,6 +112,9 @@
 	% Simple tests are in-in unifications on enumerations, integers,
 	% strings and floats.
 
+:- pred unify_gen__generate_test(var, var, code_tree, code_info, code_info).
+:- mode unify_gen__generate_test(in, in, out, in, out) is det.
+
 unify_gen__generate_test(VarA, VarB, Code) -->
 	code_info__produce_variable(VarA, Code0, ValA),
 	code_info__produce_variable(VarB, Code1, ValB),
@@ -123,7 +143,7 @@
 		{ hlds_data__get_type_defn_body(TypeDefn, TypeBody) },
 		{
 			TypeBody = du_type(_, ConsTable, _, _)
-		->  
+		->
 			map__to_assoc_list(ConsTable, ConsList),
 			(
 				ConsList = [ConsId - _, OtherConsId - _],
@@ -178,6 +198,10 @@
 
 %---------------------------------------------------------------------------%
 
+:- pred unify_gen__generate_tag_rval(var, cons_id, rval, code_tree,
+	code_info, code_info).
+:- mode unify_gen__generate_tag_rval(in, in, out, out, in, out) is det.
+
 unify_gen__generate_tag_rval(Var, ConsId, TestRval, Code) -->
         code_info__produce_variable(Var, Code, Rval),
 	code_info__cons_id_to_tag(Var, ConsId, Tag),
@@ -228,6 +252,10 @@
 	% create a term, and a series of [optional] assignments to
 	% instantiate the arguments of that term.
 
+:- pred unify_gen__generate_construction(var, cons_id,
+	list(var), list(uni_mode), code_tree, code_info, code_info).
+:- mode unify_gen__generate_construction(in, in, in, in, out, in, out) is det.
+
 unify_gen__generate_construction(Var, Cons, Args, Modes, Code) -->
 	code_info__cons_id_to_tag(Var, Cons, Tag),
 	unify_gen__generate_construction_2(Tag, Var, Args, Modes, Code).
@@ -554,6 +582,11 @@
 	% unifications are generated eagerly (they _must_ be), but
 	% assignment unifications are cached.
 
+:- pred unify_gen__generate_det_deconstruction(var, cons_id,
+	list(var), list(uni_mode), code_tree, code_info, code_info).
+:- mode unify_gen__generate_det_deconstruction(in, in, in, in, out,
+	in, out) is det.
+
 unify_gen__generate_det_deconstruction(Var, Cons, Args, Modes, Code) -->
 	code_info__cons_id_to_tag(Var, Cons, Tag),
 	% For constants, if the deconstruction is det, then we already know
@@ -615,16 +648,28 @@
 	% A semideterministic deconstruction unification is tag-test
 	% followed by a deterministic deconstruction.
 
+:- pred unify_gen__generate_semi_deconstruction(var, cons_id,
+	list(var), list(uni_mode), code_tree, code_info, code_info).
+:- mode unify_gen__generate_semi_deconstruction(in, in, in, in, out, in, out)
+	is det.
+
 unify_gen__generate_semi_deconstruction(Var, Tag, Args, Modes, Code) -->
 	unify_gen__generate_tag_test(Var, Tag, branch_on_success,
 		SuccLab, TagTestCode),
-	code_info__grab_code_info(CodeInfo),
+	code_info__remember_position(AfterUnify),
 	code_info__generate_failure(FailCode),
-	code_info__slap_code_info(CodeInfo), % XXX
+	code_info__reset_to_position(AfterUnify),
 	unify_gen__generate_det_deconstruction(Var, Tag, Args, Modes,
 		DeconsCode),
-	{ GluedCode = tree(FailCode, node([ label(SuccLab) - "" ])) },
-	{ Code = tree(TagTestCode, tree(GluedCode, DeconsCode)) }.
+	{ SuccessLabelCode = node([
+		label(SuccLab) - ""
+	]) },
+	{ Code =
+		tree(TagTestCode,
+		tree(FailCode,
+		tree(SuccessLabelCode,
+		     DeconsCode)))
+	}.
 
 %---------------------------------------------------------------------------%
 
Index: compiler/value_number.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/value_number.m,v
retrieving revision 1.93
diff -u -r1.93 value_number.m
--- value_number.m	1998/06/16 06:11:42	1.93
+++ value_number.m	1998/06/29 08:27:21
@@ -172,7 +172,7 @@
 				Target = succfr(_)
 			)
 		;
-			Uinstr0 = mkframe(_, _, _, _)
+			Uinstr0 = mkframe(_, _)
 		)
 	->
 		N1 is N0 + 1,
@@ -1076,7 +1076,7 @@
 value_number__boundary_instr(block(_, _, _), no).
 value_number__boundary_instr(assign(_,_), no).
 value_number__boundary_instr(call(_, _, _, _), yes).
-value_number__boundary_instr(mkframe(_, _, _, _), yes).
+value_number__boundary_instr(mkframe(_, _), yes).
 value_number__boundary_instr(modframe(_), yes).
 value_number__boundary_instr(label(_), yes).
 value_number__boundary_instr(goto(_), yes).
Index: compiler/vn_block.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/vn_block.m,v
retrieving revision 1.54
diff -u -r1.54 vn_block.m
--- vn_block.m	1998/06/09 02:15:05	1.54
+++ vn_block.m	1998/06/29 11:08:47
@@ -203,25 +203,27 @@
 	vn_util__rval_to_vn(Rval, Vn, VnTables0, VnTables1),
 	vn_util__lval_to_vnlval(Lval, Vnlval, VnTables1, VnTables2),
 	vn_table__set_desired_value(Vnlval, Vn, VnTables2, VnTables),
-	vn_util__find_specials(Vnlval, LeftSpecials),
-	(
-		% Assignments of this form occur in the setup for commit.
-		% We must record the left hand side (which will be a stackvar)
-		% as a must flush location, because liveness will not force
-		% it to be flushed. The reason for this is that livemap.m
-		% may be confused by an incr_sp and assignment to a similarly
-		% numbered stackvar in later code into thinking that this
-		% assignment is redundant.
-		Rval = lval(SubLval),
-		( SubLval = curfr
-		; SubLval = maxfr
-		; SubLval = redoip(_)
-		)
-	->
-		Specials = [Vnlval | LeftSpecials]
-	;
-		Specials = LeftSpecials
-	),
+	vn_util__find_specials(Vnlval, Specials),
+%	vn_util__find_specials(Vnlval, LeftSpecials),
+%	(
+%		% Assignments of this form occur in the setup for commit.
+%		% We must record the left hand side (which will be a stackvar)
+%		% as a must flush location, because liveness will not force
+%		% it to be flushed. The reason for this is that livemap.m
+%		% may be confused by an incr_sp and assignment to a similarly
+%		% numbered stackvar in later code into thinking that this
+%		% assignment is redundant.
+%		Rval = lval(SubLval),
+%		( SubLval = curfr
+%		; SubLval = maxfr
+%		; SubLval = redoip(_)
+%		; SubLval = redofr(_)
+%		)
+%	->
+%		Specials = [Vnlval | LeftSpecials]
+%	;
+%		Specials = LeftSpecials
+%	),
 	set__insert_list(Liveset0, Specials, Liveset).
 vn_block__handle_instr(call(Proc, Return, Info, CallModel),
 		Livemap, Params, VnTables0, VnTables, Liveset0, Liveset,
@@ -229,10 +231,10 @@
 	vn_block__new_ctrl_node(vn_call(Proc, Return, Info, CallModel), Livemap,
 		Params, VnTables0, VnTables,
 		Liveset0, Liveset, Tuple0, Tuple).
-vn_block__handle_instr(mkframe(Name, Size, Pragma, Redoip), Livemap, Params,
+vn_block__handle_instr(mkframe(NondetFrameInfo, Redoip), Livemap, Params,
 		VnTables0, VnTables, Liveset0, Liveset,
 		SeenIncr0, SeenIncr, Tuple0, Tuple) :-
-	vn_block__new_ctrl_node(vn_mkframe(Name, Size, Pragma, Redoip),
+	vn_block__new_ctrl_node(vn_mkframe(NondetFrameInfo, Redoip),
 		Livemap, Params, VnTables0, VnTables1,
 		Liveset0, Liveset1, Tuple0, Tuple1),
 	vn_block__handle_instr(assign(redoip(lval(maxfr)),
@@ -404,7 +406,7 @@
 		LabelNo = LabelNo0,
 		Parallels = []
 	;
-		VnInstr = vn_mkframe(_, _, _, _),
+		VnInstr = vn_mkframe(_, _),
 		VnTables = VnTables0,
 		Liveset = Liveset0,
 		FlushEntry = FlushEntry0,
@@ -800,6 +802,7 @@
 	(
 		( Vnlval = vn_field(_, _, _)
 		; Vnlval = vn_redoip(_)
+		; Vnlval = vn_redofr(_)
 		; Vnlval = vn_framevar(_)
 		; Vnlval = vn_curfr
 		; Vnlval = vn_maxfr
@@ -890,7 +893,7 @@
 vn_block__is_ctrl_instr(block(_, _, _), no).
 vn_block__is_ctrl_instr(assign(_, _), no).
 vn_block__is_ctrl_instr(call(_, _, _, _), yes).
-vn_block__is_ctrl_instr(mkframe(_, _, _, _), yes).
+vn_block__is_ctrl_instr(mkframe(_, _), yes).
 vn_block__is_ctrl_instr(modframe(_), no).
 vn_block__is_ctrl_instr(label(_), yes).
 vn_block__is_ctrl_instr(goto(_), yes).
Index: compiler/vn_cost.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/vn_cost.m,v
retrieving revision 1.33
diff -u -r1.33 vn_cost.m
--- vn_cost.m	1998/06/09 02:15:07	1.33
+++ vn_cost.m	1998/06/29 08:07:49
@@ -111,7 +111,7 @@
 		Uinstr = call(_, _, _, _),
 		Cost = 0
 	;
-		Uinstr = mkframe(_, _, _, _),
+		Uinstr = mkframe(_, _),
 		Cost = 0
 	;
 		Uinstr = modframe(_),
@@ -251,6 +251,11 @@
 		Cost is RvalCost + StackrefCost
 	;
 		Lval = prevfr(Rval),
+		vn_type__costof_stackref(Params, StackrefCost),
+		vn_cost__rval_cost(Rval, Params, RvalCost),
+		Cost is RvalCost + StackrefCost
+	;
+		Lval = redofr(Rval),
 		vn_type__costof_stackref(Params, StackrefCost),
 		vn_cost__rval_cost(Rval, Params, RvalCost),
 		Cost is RvalCost + StackrefCost
Index: compiler/vn_filter.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/vn_filter.m,v
retrieving revision 1.18
diff -u -r1.18 vn_filter.m
--- vn_filter.m	1998/06/09 02:15:10	1.18
+++ vn_filter.m	1998/06/29 08:08:10
@@ -136,7 +136,7 @@
 	error("inappropriate instruction in vn__filter").
 vn_filter__user_instr(assign(_, Rval), yes(Rval)).
 vn_filter__user_instr(call(_, _, _, _), no).
-vn_filter__user_instr(mkframe(_, _, _, _), no).
+vn_filter__user_instr(mkframe(_, _), no).
 vn_filter__user_instr(modframe(_), no).
 vn_filter__user_instr(label(_), no).
 vn_filter__user_instr(goto(_), no).
@@ -184,7 +184,7 @@
 	vn_filter__replace_in_rval(Rval0, Temp, Defn, Rval).
 vn_filter__replace_in_user_instr(call(_, _, _, _), _, _, _) :-
 	error("non-user instruction in vn_filter__replace_in_user_instr").
-vn_filter__replace_in_user_instr(mkframe(_, _, _, _), _, _, _) :-
+vn_filter__replace_in_user_instr(mkframe(_, _), _, _, _) :-
 	error("non-user instruction in vn_filter__replace_in_user_instr").
 vn_filter__replace_in_user_instr(modframe(_), _, _, _) :-
 	error("non-user instruction in vn_filter__replace_in_user_instr").
@@ -246,7 +246,7 @@
 	error("inappropriate instruction in vn__filter").
 vn_filter__defining_instr(assign(Lval, _), yes(Lval)).
 vn_filter__defining_instr(call(_, _, _, _), no).
-vn_filter__defining_instr(mkframe(_, _, _, _), no).
+vn_filter__defining_instr(mkframe(_, _), no).
 vn_filter__defining_instr(modframe(_), no).
 vn_filter__defining_instr(label(_), no).
 vn_filter__defining_instr(goto(_), no).
@@ -294,7 +294,7 @@
 	vn_filter__replace_in_lval(Lval0, Temp, Defn, Lval).
 vn_filter__replace_in_defining_instr(call(_, _, _, _), _, _, _) :-
 	error("non-def instruction in vn_filter__replace_in_defining_instr").
-vn_filter__replace_in_defining_instr(mkframe(_, _, _, _), _, _, _) :-
+vn_filter__replace_in_defining_instr(mkframe(_, _), _, _, _) :-
 	error("non-def instruction in vn_filter__replace_in_defining_instr").
 vn_filter__replace_in_defining_instr(modframe(_), _, _, _) :-
 	error("non-def instruction in vn_filter__replace_in_defining_instr").
@@ -359,6 +359,8 @@
 vn_filter__replace_in_lval(succip(Rval0), Temp, Defn, succip(Rval)) :-
 	vn_filter__replace_in_rval(Rval0, Temp, Defn, Rval).
 vn_filter__replace_in_lval(redoip(Rval0), Temp, Defn, redoip(Rval)) :-
+	vn_filter__replace_in_rval(Rval0, Temp, Defn, Rval).
+vn_filter__replace_in_lval(redofr(Rval0), Temp, Defn, redofr(Rval)) :-
 	vn_filter__replace_in_rval(Rval0, Temp, Defn, Rval).
 vn_filter__replace_in_lval(succfr(Rval0), Temp, Defn, succfr(Rval)) :-
 	vn_filter__replace_in_rval(Rval0, Temp, Defn, Rval).
Index: compiler/vn_flush.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/vn_flush.m,v
retrieving revision 1.46
diff -u -r1.46 vn_flush.m
--- vn_flush.m	1998/01/13 10:14:12	1.46
+++ vn_flush.m	1998/06/29 08:23:21
@@ -190,7 +190,7 @@
 		Templocs = Templocs0,
 		Instrs = [call(ProcAddr, RetAddr, LiveInfo, CodeModel) - ""]
 	;
-		Vn_instr = vn_mkframe(Name, Size, Pragma, Redoip),
+		Vn_instr = vn_mkframe(NondetFrameInfo, Redoip),
 		vn_util__rval_to_vn(const(code_addr_const(Redoip)), AddrVn,
 			VnTables0, VnTables1),
 		vn_util__lval_to_vnlval(redoip(lval(maxfr)), SlotVnlval,
@@ -198,7 +198,7 @@
 		vn_table__set_current_value(SlotVnlval, AddrVn,
 			VnTables2, VnTables),
 		Templocs = Templocs0,
-		Instrs = [mkframe(Name, Size, Pragma, Redoip) - ""]
+		Instrs = [mkframe(NondetFrameInfo, Redoip) - ""]
 	;
 		Vn_instr = vn_label(Label),
 		VnTables = VnTables0,
@@ -1042,6 +1042,12 @@
 			VnTables0, VnTables,
 			Templocs0, Templocs, Params, AccessInstrs),
 		Lval = prevfr(Rval)
+	;
+		Vnlval = vn_redofr(Vn1),
+		vn_flush__vn(Vn1, [src_access(Vnlval) | Srcs], Forbidden, Rval,
+			VnTables0, VnTables,
+			Templocs0, Templocs, Params, AccessInstrs),
+		Lval = redofr(Rval)
 	;
 		Vnlval = vn_redoip(Vn1),
 		vn_flush__vn(Vn1, [src_access(Vnlval) | Srcs], Forbidden, Rval,
Index: compiler/vn_order.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/vn_order.m,v
retrieving revision 1.46
diff -u -r1.46 vn_order.m
--- vn_order.m	1998/03/03 17:36:35	1.46
+++ vn_order.m	1998/06/29 08:08:26
@@ -328,7 +328,7 @@
 			Predmap1 = Predmap0,
 			VnTables1 = VnTables0
 		;
-			Vn_instr = vn_mkframe(_, _, _, _),
+			Vn_instr = vn_mkframe(_, _),
 			Succmap1 = Succmap0,
 			Predmap1 = Predmap0,
 			VnTables1 = VnTables0
Index: compiler/vn_type.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/vn_type.m,v
retrieving revision 1.38
diff -u -r1.38 vn_type.m
--- vn_type.m	1998/01/13 10:14:18	1.38
+++ vn_type.m	1998/06/29 07:36:05
@@ -27,6 +27,7 @@
 			;	vn_curfr
 			;	vn_succfr(vn)
 			;	vn_prevfr(vn)
+			;	vn_redofr(vn)
 			;	vn_redoip(vn)
 			;	vn_succip(vn)
 			;	vn_hp
@@ -70,8 +71,7 @@
 :- type vn_instr	--->	vn_livevals(lvalset)
 			;	vn_call(code_addr, code_addr,
 					list(liveinfo), call_model)
-			;	vn_mkframe(string, int, maybe(pragma_c_struct),
-					code_addr)
+			;	vn_mkframe(nondet_frame_info, code_addr)
 			;	vn_label(label)
 			;	vn_goto(code_addr)
 			;	vn_computed_goto(vn, list(label))
@@ -202,6 +202,7 @@
 vn_type__vnlval_type(vn_framevar(_), word).
 vn_type__vnlval_type(vn_succip(_), code_ptr).
 vn_type__vnlval_type(vn_redoip(_), code_ptr).
+vn_type__vnlval_type(vn_redofr(_), data_ptr).
 vn_type__vnlval_type(vn_succfr(_), data_ptr).
 vn_type__vnlval_type(vn_prevfr(_), data_ptr).
 vn_type__vnlval_type(vn_field(_, _, _), word).
Index: compiler/vn_util.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/vn_util.m,v
retrieving revision 1.61
diff -u -r1.61 vn_util.m
--- vn_util.m	1998/03/03 17:36:37	1.61
+++ vn_util.m	1998/06/29 11:11:15
@@ -44,10 +44,11 @@
 vn_util__find_specials(vn_succip, [vn_succip]).
 vn_util__find_specials(vn_maxfr, [vn_maxfr]).
 vn_util__find_specials(vn_curfr, [vn_curfr]).
+vn_util__find_specials(vn_prevfr(Vn), [vn_prevfr(Vn)]).
 vn_util__find_specials(vn_redoip(Vn), [vn_redoip(Vn)]).
+vn_util__find_specials(vn_redofr(Vn), [vn_redofr(Vn)]).
 vn_util__find_specials(vn_succip(Vn), [vn_succip(Vn)]).
 vn_util__find_specials(vn_succfr(Vn), [vn_succfr(Vn)]).
-vn_util__find_specials(vn_prevfr(Vn), [vn_prevfr(Vn)]).
 vn_util__find_specials(vn_hp, [vn_hp]).
 vn_util__find_specials(vn_sp, [vn_sp]).
 vn_util__find_specials(vn_field(_, _, _), []).
@@ -939,18 +940,21 @@
 	; Lval = mem_ref(Rval1) ->
 		vn_util__rval_to_vn(Rval1, Vn1, VnTables0, VnTables),
 		Vnlval = vn_mem_ref(Vn1)
-	; Lval = succfr(Rval1) ->
-		vn_util__rval_to_vn(Rval1, Vn1, VnTables0, VnTables),
-		Vnlval = vn_succfr(Vn1)
 	; Lval = prevfr(Rval1) ->
 		vn_util__rval_to_vn(Rval1, Vn1, VnTables0, VnTables),
 		Vnlval = vn_prevfr(Vn1)
 	; Lval = redoip(Rval1) ->
 		vn_util__rval_to_vn(Rval1, Vn1, VnTables0, VnTables),
 		Vnlval = vn_redoip(Vn1)
+	; Lval = redofr(Rval1) ->
+		vn_util__rval_to_vn(Rval1, Vn1, VnTables0, VnTables),
+		Vnlval = vn_redofr(Vn1)
 	; Lval = succip(Rval1) ->
 		vn_util__rval_to_vn(Rval1, Vn1, VnTables0, VnTables),
 		Vnlval = vn_succip(Vn1)
+	; Lval = succfr(Rval1) ->
+		vn_util__rval_to_vn(Rval1, Vn1, VnTables0, VnTables),
+		Vnlval = vn_succfr(Vn1)
 	;
 		error("unexpected lval in vn_util__lval_to_vnlval")
 	).
@@ -967,9 +971,10 @@
 vn_util__no_access_lval_to_vnlval(succip,		yes(vn_succip)).
 vn_util__no_access_lval_to_vnlval(maxfr,		yes(vn_maxfr)).
 vn_util__no_access_lval_to_vnlval(curfr,		yes(vn_curfr)).
+vn_util__no_access_lval_to_vnlval(prevfr(_),		no).
 vn_util__no_access_lval_to_vnlval(redoip(_),		no).
+vn_util__no_access_lval_to_vnlval(redofr(_),		no).
 vn_util__no_access_lval_to_vnlval(succip(_),		no).
-vn_util__no_access_lval_to_vnlval(prevfr(_),		no).
 vn_util__no_access_lval_to_vnlval(succfr(_),		no).
 vn_util__no_access_lval_to_vnlval(hp,			yes(vn_hp)).
 vn_util__no_access_lval_to_vnlval(sp,			yes(vn_sp)).
@@ -985,10 +990,11 @@
 vn_util__no_access_vnlval_to_lval(vn_succip,		yes(succip)).
 vn_util__no_access_vnlval_to_lval(vn_maxfr,		yes(maxfr)).
 vn_util__no_access_vnlval_to_lval(vn_curfr,		yes(curfr)).
-vn_util__no_access_vnlval_to_lval(vn_succfr(_),		no).
-vn_util__no_access_vnlval_to_lval(vn_prevfr(_),		no).
+vn_util__no_access_vnlval_to_lval(vn_redofr(_),		no).
 vn_util__no_access_vnlval_to_lval(vn_redoip(_),		no).
+vn_util__no_access_vnlval_to_lval(vn_prevfr(_),		no).
 vn_util__no_access_vnlval_to_lval(vn_succip(_),		no).
+vn_util__no_access_vnlval_to_lval(vn_succfr(_),		no).
 vn_util__no_access_vnlval_to_lval(vn_hp,		yes(hp)).
 vn_util__no_access_vnlval_to_lval(vn_sp,		yes(sp)).
 vn_util__no_access_vnlval_to_lval(vn_field(_, _, _),	no).
@@ -1002,10 +1008,11 @@
 vn_util__vnlval_access_vns(vn_succip, []).
 vn_util__vnlval_access_vns(vn_maxfr, []).
 vn_util__vnlval_access_vns(vn_curfr, []).
-vn_util__vnlval_access_vns(vn_succfr(Vn), [Vn]).
 vn_util__vnlval_access_vns(vn_prevfr(Vn), [Vn]).
 vn_util__vnlval_access_vns(vn_redoip(Vn), [Vn]).
+vn_util__vnlval_access_vns(vn_redofr(Vn), [Vn]).
 vn_util__vnlval_access_vns(vn_succip(Vn), [Vn]).
+vn_util__vnlval_access_vns(vn_succfr(Vn), [Vn]).
 vn_util__vnlval_access_vns(vn_hp, []).
 vn_util__vnlval_access_vns(vn_sp, []).
 vn_util__vnlval_access_vns(vn_field(_, Vn1, Vn2), [Vn1, Vn2]).
@@ -1179,10 +1186,11 @@
 vn_util__classify_loc_cost(vn_succip, 0).
 vn_util__classify_loc_cost(vn_maxfr, 0).
 vn_util__classify_loc_cost(vn_curfr, 0).
-vn_util__classify_loc_cost(vn_succfr(_), 1).
 vn_util__classify_loc_cost(vn_prevfr(_), 1).
 vn_util__classify_loc_cost(vn_redoip(_), 1).
+vn_util__classify_loc_cost(vn_redofr(_), 1).
 vn_util__classify_loc_cost(vn_succip(_), 1).
+vn_util__classify_loc_cost(vn_succfr(_), 1).
 vn_util__classify_loc_cost(vn_hp, 0).
 vn_util__classify_loc_cost(vn_sp, 0).
 vn_util__classify_loc_cost(vn_field(_, _, _), 2).
@@ -1219,7 +1227,7 @@
 			VnInstr = vn_call(_, _, _, _),
 			VnTables1 = VnTables0
 		;
-			VnInstr = vn_mkframe(_, _, _, _),
+			VnInstr = vn_mkframe(_, _),
 			VnTables1 = VnTables0
 		;
 			VnInstr = vn_label(_),
Index: compiler/vn_verify.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/vn_verify.m,v
retrieving revision 1.17
diff -u -r1.17 vn_verify.m
--- vn_verify.m	1998/05/16 07:31:20	1.17
+++ vn_verify.m	1998/06/29 11:12:25
@@ -211,10 +211,11 @@
 vn_verify__subst_access_vns(vn_succip, [], succip).
 vn_verify__subst_access_vns(vn_maxfr, [], maxfr).
 vn_verify__subst_access_vns(vn_curfr, [], curfr).
-vn_verify__subst_access_vns(vn_succfr(_), [R], succfr(R)).
 vn_verify__subst_access_vns(vn_prevfr(_), [R], prevfr(R)).
 vn_verify__subst_access_vns(vn_redoip(_), [R], redoip(R)).
+vn_verify__subst_access_vns(vn_redofr(_), [R], redofr(R)).
 vn_verify__subst_access_vns(vn_succip(_), [R], succip(R)).
+vn_verify__subst_access_vns(vn_succfr(_), [R], succfr(R)).
 vn_verify__subst_access_vns(vn_hp, [], hp).
 vn_verify__subst_access_vns(vn_sp, [], sp).
 vn_verify__subst_access_vns(vn_field(T, _, _), [R1, R2], field(T, R1, R2)).
@@ -298,7 +299,7 @@
 		NoDeref = NoDeref0,
 		Tested = Tested0
 	;
-		Instr = mkframe(_, _, _, _),
+		Instr = mkframe(_, _),
 		NoDeref = NoDeref0,
 		Tested = Tested0
 	;
@@ -386,13 +387,15 @@
 vn_verify__tags_lval(succip, _).
 vn_verify__tags_lval(maxfr, _).
 vn_verify__tags_lval(curfr, _).
-vn_verify__tags_lval(succip(Rval), NoDeref) :-
+vn_verify__tags_lval(prevfr(Rval), NoDeref) :-
 	vn_verify__tags_rval(Rval, NoDeref).
 vn_verify__tags_lval(redoip(Rval), NoDeref) :-
 	vn_verify__tags_rval(Rval, NoDeref).
-vn_verify__tags_lval(succfr(Rval), NoDeref) :-
+vn_verify__tags_lval(redofr(Rval), NoDeref) :-
 	vn_verify__tags_rval(Rval, NoDeref).
-vn_verify__tags_lval(prevfr(Rval), NoDeref) :-
+vn_verify__tags_lval(succip(Rval), NoDeref) :-
+	vn_verify__tags_rval(Rval, NoDeref).
+vn_verify__tags_lval(succfr(Rval), NoDeref) :-
 	vn_verify__tags_rval(Rval, NoDeref).
 vn_verify__tags_lval(hp, _).
 vn_verify__tags_lval(sp, _).



More information about the developers mailing list