[m-dev.] for review: fix value numbering with structure reuse

Simon Taylor stayl at cs.mu.OZ.AU
Mon Feb 7 15:03:03 AEDT 2000



Estimated hours taken: 1

Restrict value numbering on procedures containing reconstructions.
Without this change, value numbering could reorder instructions
which extract fields from a cell with the instructions which update
the values of those fields.

compiler/llds.m:
	Add a field to each `c_procedure' to record whether the
	procedure contains a reconstruction.

compiler/code_gen.m:
	Fill in the field.

compiler/value_number.m:
	Wrap labels around all field assignments in procedures which
	contain reconstructions.

compiler/*.m:
	Handle the extra field of the `c_procedure' constructor.


Index: code_gen.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/code_gen.m,v
retrieving revision 1.72
diff -u -u -r1.72 code_gen.m
--- code_gen.m	2000/01/26 02:04:23	1.72
+++ code_gen.m	2000/02/04 05:58:08
@@ -64,7 +64,7 @@
 :- import_module par_conj_gen, pragma_c_gen, commit_gen.
 :- import_module continuation_info, trace, options, hlds_out.
 :- import_module code_aux, middle_rec, passes_aux, llds_out.
-:- import_module code_util, type_util, mode_util.
+:- import_module code_util, type_util, mode_util, goal_util.
 :- import_module prog_data, prog_out, instmap.
 :- import_module bool, char, int, string.
 :- import_module map, assoc_list, set, term, tree, std_util, require, varset.
@@ -260,8 +260,16 @@
 
 	pred_info_name(PredInfo, Name),
 	pred_info_arity(PredInfo, Arity),
+
+	( goal_contains_reconstruction(Goal) ->
+		ContainsReconstruction = contains_reconstruction
+	;
+		ContainsReconstruction = does_not_contain_reconstruction
+	),
+
 		% Construct a c_procedure structure with all the information.
-	Proc = c_procedure(Name, Arity, proc(PredId, ProcId), Instructions).
+	Proc = c_procedure(Name, Arity, proc(PredId, ProcId),
+		Instructions, ContainsReconstruction).
 
 :- pred maybe_add_tabling_pointer_var(module_info, pred_id, proc_id, proc_info,
 		global_data, global_data).
Index: continuation_info.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/continuation_info.m,v
retrieving revision 1.29
diff -u -u -r1.29 continuation_info.m
--- continuation_info.m	1999/12/14 04:52:36	1.29
+++ continuation_info.m	2000/02/04 05:39:40
@@ -297,7 +297,7 @@
 
 continuation_info__maybe_process_llds([], _) --> [].
 continuation_info__maybe_process_llds([Proc | Procs], ModuleInfo) -->
-	{ Proc = c_procedure(_, _, PredProcId, Instrs) },
+	{ Proc = c_procedure(_, _, PredProcId, Instrs, _) },
 	continuation_info__maybe_process_proc_llds(Instrs, PredProcId,
 		ModuleInfo),
 	continuation_info__maybe_process_llds(Procs, ModuleInfo).
Index: llds.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/llds.m,v
retrieving revision 1.256
diff -u -u -r1.256 llds.m
--- llds.m	2000/01/14 01:10:23	1.256
+++ llds.m	2000/02/04 05:28:38
@@ -163,8 +163,17 @@
 			string,			% predicate name
 			int,			% arity
 			pred_proc_id,		% the pred_proc_id this code
-			list(instruction)	% the code for this procedure
+			list(instruction),	% the code for this procedure
+			contains_reconstruction	% value numbering needs
+						% to handle goals that
+						% perform structure reuse
+						% specially.
 		).
+
+:- type contains_reconstruction
+	--->	contains_reconstruction
+	;	does_not_contain_reconstruction
+	.
 
 :- type llds_proc_id	==	int.
 
Index: llds_common.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/llds_common.m,v
retrieving revision 1.27
diff -u -u -r1.27 llds_common.m
--- llds_common.m	2000/01/14 01:10:26	1.27
+++ llds_common.m	2000/02/04 05:28:39
@@ -136,9 +136,9 @@
 	common_info::in, common_info::out) is det.
 
 llds_common__process_proc(Proc0, Proc, Info0, Info) :-
-	Proc0 = c_procedure(Name, Arity, PredProcId, Instrs0),
+	Proc0 = c_procedure(Name, Arity, PredProcId, Instrs0, Reconstruction),
 	llds_common__process_instrs(Instrs0, Instrs, Info0, Info),
-	Proc = c_procedure(Name, Arity, PredProcId, Instrs).
+	Proc = c_procedure(Name, Arity, PredProcId, Instrs, Reconstruction).
 
 :- pred llds_common__process_instrs(list(instruction)::in,
 	list(instruction)::out, common_info::in, common_info::out) is det.
Index: llds_out.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/llds_out.m,v
retrieving revision 1.134
diff -u -u -r1.134 llds_out.m
--- llds_out.m	2000/01/14 01:10:27	1.134
+++ llds_out.m	2000/02/04 05:28:40
@@ -1085,7 +1085,7 @@
 :- mode output_c_procedure_decls(in, in, out, di, uo) is det.
 
 output_c_procedure_decls(Proc, DeclSet0, DeclSet) -->
-	{ Proc = c_procedure(_Name, _Arity, _PredProcId, Instrs) },
+	{ Proc = c_procedure(_Name, _Arity, _PredProcId, Instrs, _Recons) },
 	output_instruction_list_decls(Instrs, DeclSet0, DeclSet).
 
 :- pred output_c_procedure(c_procedure, bool, bool,
@@ -1093,7 +1093,8 @@
 :- mode output_c_procedure(in, in, in, di, uo) is det.
 
 output_c_procedure(Proc, PrintComments, EmitCLoops) -->
-	{ Proc = c_procedure(Name, Arity, proc(_PredId, ProcId), Instrs) },
+	{ Proc = c_procedure(Name, Arity, proc(_PredId, ProcId),
+			Instrs, _Recons) },
 	{ proc_id_to_int(ProcId, ModeNum) },
 	( { PrintComments = yes } ->
 		io__write_string("\n/*-------------------------------------"),
@@ -4192,7 +4193,7 @@
 	list(label)::in, list(label)::out) is det.
 
 gather_labels_from_c_procs([], Labels, Labels).
-gather_labels_from_c_procs([c_procedure(_, _, _, Instrs) | Procs],
+gather_labels_from_c_procs([c_procedure(_, _, _, Instrs, _) | Procs],
 		Labels0, Labels) :-
 	gather_labels_from_instrs(Instrs, Labels0, Labels1),
 	gather_labels_from_c_procs(Procs, Labels1, Labels).
Index: mercury_compile.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/mercury_compile.m,v
retrieving revision 1.147
diff -u -u -r1.147 mercury_compile.m
--- mercury_compile.m	2000/01/10 00:43:44	1.147
+++ mercury_compile.m	2000/02/04 06:01:46
@@ -1272,7 +1272,7 @@
 	;
 		{ Proc = Proc0 }
 	),
-	{ Proc = c_procedure(_, _, PredProcId, Instructions) },
+	{ Proc = c_procedure(_, _, PredProcId, Instructions, _) },
 	write_proc_progress_message(
 		"% Generating call continuation information for ",
 			PredId, ProcId, ModuleInfo3),
Index: optimize.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/optimize.m,v
retrieving revision 1.21
diff -u -u -r1.21 optimize.m
--- optimize.m	1999/12/14 04:52:51	1.21
+++ optimize.m	2000/02/04 06:05:39
@@ -40,7 +40,8 @@
 	optimize_main(Procs0, GlobalData, Procs).
 
 optimize__proc(CProc0, GlobalData, CProc) -->
-	{ CProc0 = c_procedure(Name, Arity, PredProcId, Instrs0) },
+	{ CProc0 = c_procedure(Name, Arity, PredProcId,
+			Instrs0, ContainsReconstruction) },
 	globals__io_lookup_bool_option(debug_opt, DebugOpt),
 	opt_debug__msg(DebugOpt, "before optimization"),
 	opt_debug__dump_instrs(DebugOpt, Instrs0),
@@ -60,26 +61,28 @@
 	},
 	( { ValueNumber = yes } ->
 		{ NovnRepeat is AllRepeat - VnRepeat },
-		optimize__repeat(NovnRepeat, no,  LayoutLabelSet,
-			Instrs0, Instrs1),
+		optimize__repeat(NovnRepeat, no, ContainsReconstruction,
+			LayoutLabelSet, Instrs0, Instrs1),
 		optimize__middle(Instrs1, no, LayoutLabelSet, Instrs2),
-		optimize__repeat(VnRepeat, yes, LayoutLabelSet,
-			Instrs2, Instrs3)
+		optimize__repeat(VnRepeat, yes, ContainsReconstruction,
+			LayoutLabelSet, Instrs2, Instrs3)
 	;
-		optimize__repeat(AllRepeat, no,  LayoutLabelSet,
-			Instrs0, Instrs1),
+		optimize__repeat(AllRepeat, no, ContainsReconstruction,
+			LayoutLabelSet, Instrs0, Instrs1),
 		optimize__middle(Instrs1, yes, LayoutLabelSet, Instrs3)
 	),
 	optimize__last(Instrs3, LayoutLabelSet, Instrs),
-	{ CProc = c_procedure(Name, Arity, PredProcId, Instrs) }.
+	{ CProc = c_procedure(Name, Arity, PredProcId, Instrs,
+			ContainsReconstruction) }.
 
 %-----------------------------------------------------------------------------%
 
-:- pred optimize__repeat(int::in, bool::in, set(label)::in,
-	list(instruction)::in, list(instruction)::out,
+:- pred optimize__repeat(int::in, bool::in, contains_reconstruction::in,
+	set(label)::in, list(instruction)::in, list(instruction)::out,
 	io__state::di, io__state::uo) is det.
 
-optimize__repeat(Iter0, DoVn, LayoutLabelSet, Instrs0, Instrs) -->
+optimize__repeat(Iter0, DoVn, ContainsReconstruction,
+		LayoutLabelSet, Instrs0, Instrs) -->
 	(
 		{ Iter0 > 0 }
 	->
@@ -89,11 +92,11 @@
 		;
 			{ Final = no }
 		),
-		optimize__repeated(Instrs0, DoVn, Final, LayoutLabelSet,
-			Instrs1, Mod),
+		optimize__repeated(Instrs0, DoVn, ContainsReconstruction,
+			Final, LayoutLabelSet, Instrs1, Mod),
 		( { Mod = yes } ->
-			optimize__repeat(Iter1, DoVn, LayoutLabelSet,
-				Instrs1, Instrs)
+			optimize__repeat(Iter1, DoVn, ContainsReconstruction,
+				LayoutLabelSet, Instrs1, Instrs)
 		;
 			{ Instrs = Instrs1 }
 		)
@@ -104,11 +107,13 @@
 	% We short-circuit jump sequences before normal peepholing
 	% to create more opportunities for use of the tailcall macro.
 
-:- pred optimize__repeated(list(instruction)::in, bool::in, bool::in,
+:- pred optimize__repeated(list(instruction)::in, bool::in,
+	contains_reconstruction::in, bool::in,
 	set(label)::in, list(instruction)::out, bool::out,
 	io__state::di, io__state::uo) is det.
 
-optimize__repeated(Instrs0, DoVn, Final, LayoutLabelSet, Instrs, Mod) -->
+optimize__repeated(Instrs0, DoVn, ContainsReconstruction,
+		Final, LayoutLabelSet, Instrs, Mod) -->
 	globals__io_lookup_bool_option(very_verbose, VeryVerbose),
 	globals__io_lookup_bool_option(debug_opt, DebugOpt),
 	{ opt_util__find_first_label(Instrs0, Label) },
@@ -123,7 +128,8 @@
 		;
 			[]
 		),
-		value_number_main(Instrs0, LayoutLabelSet, Instrs1),
+		value_number_main(Instrs0, ContainsReconstruction,
+			LayoutLabelSet, Instrs1),
 		( { Instrs1 = Instrs0 } ->
 			[]
 		;
Index: transform_llds.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/transform_llds.m,v
retrieving revision 1.4
diff -u -u -r1.4 transform_llds.m
--- transform_llds.m	1999/07/10 07:19:54	1.4
+++ transform_llds.m	2000/02/04 05:54:26
@@ -90,8 +90,9 @@
 :- pred transform_c_procedure(c_procedure, c_procedure, io__state, io__state).
 :- mode transform_c_procedure(in, out, di, uo) is det.
 
-transform_c_procedure(c_procedure(Name, Arity, PredProcId, Instructions0),
-		c_procedure(Name, Arity, PredProcId, Instructions)) -->
+transform_c_procedure(
+		c_procedure(Name, Arity, PredProcId, Instructions0, Recons),
+		c_procedure(Name, Arity, PredProcId, Instructions, Recons)) -->
 	transform_instructions(Instructions0, Instructions).
 
 %-----------------------------------------------------------------------------%

Index: value_number.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/value_number.m,v
retrieving revision 1.101
diff -u -u -r1.101 value_number.m
--- value_number.m	2000/01/14 01:10:52	1.101
+++ value_number.m	2000/02/07 03:56:40
@@ -20,9 +20,9 @@
 	% Find straight-line code sequences and optimize them using
 	% value numbering.
 
-:- pred value_number_main(list(instruction), set(label), list(instruction),
-	io__state, io__state).
-:- mode value_number_main(in, in, out, di, uo) is det.
+:- pred value_number_main(list(instruction), contains_reconstruction,
+		set(label), list(instruction), io__state, io__state).
+:- mode value_number_main(in, in, in, out, di, uo) is det.
 
 	% The main value numbering pass introduces references to temporary
 	% variables whose values need be preserved only within an extended
@@ -51,12 +51,13 @@
 	% We can't find out what variables are used by C code sequences,
 	% so we don't optimize any predicates containing them.
 
-value_number_main(Instrs0, LayoutLabelSet, Instrs) -->
+value_number_main(Instrs0, ContainsReconstruction, LayoutLabelSet, Instrs) -->
 	{ opt_util__get_prologue(Instrs0, ProcLabel,
 		LabelInstr, Comments, Instrs1) },
 	{ opt_util__new_label_no(Instrs1, 1000, N0) },
 	{ value_number__prepare_for_vn([LabelInstr | Instrs1], ProcLabel,
-		no, AllocSet, BreakSet, N0, N, Instrs2) },
+		no, ContainsReconstruction, AllocSet, BreakSet,
+		N0, N, Instrs2) },
 	{ labelopt__build_useset(Instrs2, LayoutLabelSet, UseSet) },
 	{ livemap__build(Instrs2, MaybeLiveMap) },
 	(
@@ -117,16 +118,26 @@
 	% Operations on a cell which is explicitly freed by a free_heap 
 	% instruction should not be reordered with the free_heap.
 	% We put labels before and after to avoid this.
-
-:- pred value_number__prepare_for_vn(list(instruction), proc_label,
-	bool, set(label), set(label), int, int, list(instruction)).
-:- mode value_number__prepare_for_vn(in, in, in, out, out, in, out, out) is det.
+	%
+	% If the instruction list destructively updates a cell, we need
+	% to be careful not to recorder extractions of fields of the
+	% updated cell with the update. To do this, we put labels
+	% before and after `assign' instructions for which the destination
+	% is a `field' lval. The test for this case below is a bit too
+	% conservative -- we could mark the assignments which need to be
+	% treated this way during code generation.
+
+:- pred value_number__prepare_for_vn(list(instruction), proc_label, bool,
+	contains_reconstruction, set(label), set(label),
+	int, int, list(instruction)).
+:- mode value_number__prepare_for_vn(in, in, in, in,
+	out, out, in, out, out) is det.
 
-value_number__prepare_for_vn([], _, _, AllocSet, BreakSet, N, N, []) :-
+value_number__prepare_for_vn([], _, _, _, AllocSet, BreakSet, N, N, []) :-
 	set__init(AllocSet),
 	set__init(BreakSet).
-value_number__prepare_for_vn([Instr0 | Instrs0], ProcLabel,
-		SeenAlloc, AllocSet, BreakSet, N0, N, Instrs) :-
+value_number__prepare_for_vn([Instr0 | Instrs0], ProcLabel, SeenAlloc,
+		ContainsReconstruction, AllocSet, BreakSet, N0, N, Instrs) :-
 	Instr0 = Uinstr0 - _Comment,
 	( Uinstr0 = if_val(Test, TrueAddr) ->
 		( ( TrueAddr = do_redo ; TrueAddr = do_fail ) ->
@@ -148,8 +159,9 @@
 		FalseAddr = label(FalseLabel),
 		value_number__breakup_complex_if(Test, TrueAddr, FalseAddr,
 			FalseAddr, ProcLabel, N2, N3, IfInstrs),
-		value_number__prepare_for_vn(Instrs0, ProcLabel,
-			SeenAlloc, AllocSet, BreakSet0, N3, N, Instrs1),
+		value_number__prepare_for_vn(Instrs0, ProcLabel, SeenAlloc,
+			ContainsReconstruction, AllocSet, BreakSet0,
+			N3, N, Instrs1),
 		( MaybeNewFalseLabel = yes(NewFalseLabel) ->
 			FalseInstr = label(NewFalseLabel) - "vn false label",
 			list__append(IfInstrs, [FalseInstr | Instrs1], Instrs2)
@@ -170,13 +182,15 @@
 			N1 is N0 + 1,
 			NewLabel = local(ProcLabel, N0),
 			value_number__prepare_for_vn(Instrs0, ProcLabel,
-				yes, AllocSet0, BreakSet, N1, N, Instrs1),
+				yes, ContainsReconstruction,
+				AllocSet0, BreakSet, N1, N, Instrs1),
 			set__insert(AllocSet0, NewLabel, AllocSet),
 			LabelInstr = label(NewLabel) - "vn incr divide label",
 			Instrs = [LabelInstr, Instr0 | Instrs1]
 		;
-			value_number__prepare_for_vn(Instrs0, ProcLabel,
-				yes, AllocSet, BreakSet, N0, N, Instrs1),
+			value_number__prepare_for_vn(Instrs0, ProcLabel, yes,
+				ContainsReconstruction, AllocSet, BreakSet,
+				N0, N, Instrs1),
 			Instrs = [Instr0 | Instrs1]
 		)
 	;
@@ -194,6 +208,10 @@
 				Target = prevfr(_)
 			;
 				Target = succfr(_)
+			;
+				Target = field(_, _, _),
+				ContainsReconstruction =
+					contains_reconstruction
 			)
 		;
 			Uinstr0 = mkframe(_, _)
@@ -207,14 +225,16 @@
 		N2 is N1 + 1,
 		AfterLabel = local(ProcLabel, N1),
 		AfterInstr = label(AfterLabel) - "vn stack ctrl after label",
-		value_number__prepare_for_vn(Instrs0, ProcLabel,
-			yes, AllocSet, BreakSet0, N2, N, Instrs1),
+		value_number__prepare_for_vn(Instrs0, ProcLabel, yes,
+			ContainsReconstruction, AllocSet, BreakSet0,
+			N2, N, Instrs1),
 		set__insert(BreakSet0, BeforeLabel, BreakSet1),
 		set__insert(BreakSet1, AfterLabel, BreakSet),
 		Instrs = [BeforeInstr, Instr0, AfterInstr | Instrs1]
 	;
-		value_number__prepare_for_vn(Instrs0, ProcLabel,
-			SeenAlloc, AllocSet, BreakSet, N0, N, Instrs1),
+		value_number__prepare_for_vn(Instrs0, ProcLabel, SeenAlloc,
+			ContainsReconstruction, AllocSet,
+			BreakSet, N0, N, Instrs1),
 		Instrs = [Instr0 | Instrs1]
 	).
 
--------------------------------------------------------------------------
mercury-developers mailing list
Post messages to:       mercury-developers at cs.mu.oz.au
Administrative Queries: owner-mercury-developers at cs.mu.oz.au
Subscriptions:          mercury-developers-request at cs.mu.oz.au
--------------------------------------------------------------------------



More information about the developers mailing list