[m-dev.] for review: MLDS backend to do structure reuse and compile time gc

Simon Taylor stayl at cs.mu.OZ.AU
Mon Oct 9 15:33:11 AEDT 2000


I wrote:
> Peter Ross wrote:
> > Simon, is it possible for you to check you changes for generating LLDS
> > code which does reuse in?
> 
> It's probably better if I send you a diff, which you can test then check in.

I've just looked at it again, and it probably isn't much use to you.
The changes I made were to the old code generator (code_exprn.m).
For structure reuse it's much better to use var_locn.m, because
you don't need to worry about the code generator reordering code to
extract arguments from a cell with code to reuse the cell.
All the changes to unify_gen.m below to deal with flushing arguments
of deconstructions are no longer needed.

Simon.


Index: compiler/code_exprn.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/code_exprn.m,v
retrieving revision 1.51.4.9
diff -u -u -r1.51.4.9 code_exprn.m
--- compiler/code_exprn.m	2000/01/17 22:51:46	1.51.4.9
+++ compiler/code_exprn.m	2000/01/18 12:57:56
@@ -1088,6 +1088,7 @@
 code_exprn__expr_is_constant(create(Tag, Args0, ArgTypes, StatDyn,
 		Label, Msg, Reuse),
 		Vars, ExprnOpts, NewRval) :-
+	StatDyn \= must_be_dynamic,
 	Reuse = no,
 	( StatDyn = must_be_static ->
 		NewRval = create(Tag, Args0, ArgTypes, StatDyn,
@@ -1566,9 +1567,6 @@
 		{ Rval = create(Tag, Rvals, ArgTypes, _StatDyn, _Label,
 			Msg, Reuse) }
 	->
-		{ require(unify(Reuse, no),
-	"code_exprn__construct_code: structure reuse not yet implemented") },
-
 		{ require(lambda([] is semidet,
 			(llds__all_args_are_word_size(ArgTypes, yes))),
 		"trying to construct heap cell with non-word-size arg(s)") },
@@ -1584,7 +1582,7 @@
 			( { Lval = field(_, _, _) } ->
 				code_exprn__acquire_reg(r, Reg),
 				code_exprn__construct_cell(Reg, VarName,
-					Tag, Arity, Rvals, Msg, Code0),
+					Tag, Arity, Rvals, Msg, Reuse, Code0),
 				{ string__append(VarName, " placement",
 					Comment) },
 				{ Code1 = node([
@@ -1594,7 +1592,7 @@
 				code_exprn__release_reg(Reg)
 			;
 				code_exprn__construct_cell(Lval, VarName,
-					Tag, Arity, Rvals, Msg, Code)
+					Tag, Arity, Rvals, Msg, Reuse, Code)
 			)
 		)
 	;
@@ -1603,17 +1601,29 @@
 	).
 
 :- pred code_exprn__construct_cell(lval, string, tag, int, list(maybe(rval)),
-	string, code_tree, exprn_info, exprn_info).
-:- mode code_exprn__construct_cell(in, in, in, in, in, in, out, in, out) is det.
-
-code_exprn__construct_cell(Lval, VarName, Tag, Arity, Rvals, TypeMsg, Code) -->
-	{ string__append("Allocating heap for ", VarName, Comment) },
-	{ Code0 = node([
-		incr_hp(Lval, yes(Tag), const(int_const(Arity)), TypeMsg)
-			- Comment
-	]) },
-	code_exprn__construct_args(Rvals, Tag, Lval, 0, Targets, Code1),
-	code_exprn__free_arg_dependenciess(Targets),
+	string, maybe(rval), code_tree, exprn_info, exprn_info).
+:- mode code_exprn__construct_cell(in, in, in, in, in,
+	in, in, out, in, out) is det.
+
+code_exprn__construct_cell(Lval, VarName, Tag, Arity, Rvals,
+		TypeMsg, MaybeReuse, Code) -->
+	( { MaybeReuse = yes(Reuse) } ->
+		code_exprn__place_exprn(yes(Lval), no, Reuse, no, no,
+			ReuseCellLval, Code0),
+		code_exprn__construct_args(Rvals, Tag, Lval,
+			0, Targets, Code1),
+		code_exprn__free_arg_dependenciess(Targets),
+		code_exprn__rem_lval_reg_dependencies(ReuseCellLval)
+	;
+		{ string__append("Allocating heap for ", VarName, Comment) },
+		{ Code0 = node([
+			incr_hp(Lval, yes(Tag), const(int_const(Arity)),
+				TypeMsg) - Comment
+		]) },
+		code_exprn__construct_args(Rvals, Tag, Lval,
+			0, Targets, Code1),
+		code_exprn__free_arg_dependenciess(Targets)
+	),
 	{ Code = tree(Code0, Code1) }.
 
 :- pred code_exprn__construct_args(list(maybe(rval)), int, lval, int,
@@ -2005,14 +2015,20 @@
 	->
 		{ Stat = Stat0 }
 	;
-		code_exprn__get_var_name(Var, Name),
-		{ term__var_to_int(Var, Num) },
-		{ string__int_to_string(Num, NumStr) },
-		{ string__append_list(["variable ", Name, " (", NumStr,
-			") not found"], Msg) },
-		{ error(Msg) }
+		code_exprn__var_not_found(Var)
 	).
 
+:- pred code_exprn__var_not_found(prog_var, exprn_info, exprn_info).
+:- mode code_exprn__var_not_found(in, in, out) is erroneous.
+	
+code_exprn__var_not_found(Var) -->
+	code_exprn__get_var_name(Var, Name),
+	{ term__var_to_int(Var, Num) },
+	{ string__int_to_string(Num, NumStr) },
+	{ string__append_list(["variable ", Name, " (", NumStr,
+		") not found"], Msg) },
+	{ error(Msg) }.
+
 :- pred code_exprn__maybe_set_evaled(maybe(prog_var), list(rval),
 	exprn_info, exprn_info).
 :- mode code_exprn__maybe_set_evaled(in, in, in, out) is det.
@@ -2030,7 +2046,8 @@
 	{ map__set(Vars0, Var, var_info(Refs, Stat), Vars) },
 	code_exprn__set_vars(Vars).
 
-:- pred code_exprn__maybe_add_evaled(maybe(prog_var), rval, exprn_info, exprn_info).
+:- pred code_exprn__maybe_add_evaled(maybe(prog_var),
+		rval, exprn_info, exprn_info).
 :- mode code_exprn__maybe_add_evaled(in, in, in, out) is det.
 
 code_exprn__maybe_add_evaled(no, _) --> [].
Index: compiler/unify_gen.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/unify_gen.m,v
retrieving revision 1.83.2.21
diff -u -u -r1.83.2.21 unify_gen.m
--- compiler/unify_gen.m	2000/01/17 22:54:26	1.83.2.21
+++ compiler/unify_gen.m	2000/01/20 06:37:36
@@ -18,15 +18,15 @@
 
 :- interface.
 
-:- import_module hlds_goal, hlds_data, llds, code_info, instmap.
+:- import_module hlds_goal, hlds_data, llds, code_info.
 :- import_module prog_data.
 
 :- type test_sense
 	--->	branch_on_success
 	;	branch_on_failure.
 
-:- pred unify_gen__generate_unification(code_model, unification, instmap_delta,
-	code_tree, code_info, code_info).
+:- pred unify_gen__generate_unification(code_model, unification,
+	hlds_goal_info, code_tree, code_info, code_info).
 :- mode unify_gen__generate_unification(in, in, in, out, in, out) is det.
 
 :- pred unify_gen__generate_tag_test(prog_var, cons_id, test_sense, label,
@@ -40,36 +40,39 @@
 :- import_module builtin_ops, inst_table.
 :- 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 globals, options, continuation_info, stack_layout, inst_match.
+:- import_module globals, options, continuation_info, stack_layout.
+:- import_module (inst), instmap, inst_match.
 
-:- import_module term, bool, string, int, list, map, require, std_util.
+:- import_module term, bool, string, int, list, map, require, set, std_util.
 
 :- type uni_val		--->	ref(prog_var)
 			;	lval(lval).
 
 %---------------------------------------------------------------------------%
 
-unify_gen__generate_unification(CodeModel, Uni, IMD, Code) -->
+unify_gen__generate_unification(CodeModel, Uni, GoalInfo, Code) -->
 	{ CodeModel = model_non ->
 		error("nondet unification in unify_gen__generate_unification")
 	;
 		true
 	},
+	{ goal_info_get_instmap_delta(GoalInfo, IMD) },
 	(
 		{ Uni = assign(Left, Right) },
 		unify_gen__generate_assignment(Left, Right, Code)
 	;
-		{ Uni = construct(Var, ConsId, Args, Modes, _, _, AditiInfo) },
+		{ Uni = construct(Var, ConsId, Args, Modes,
+				Reuse, Unique, AditiInfo) },
 		unify_gen__generate_construction(Var, ConsId,
-			Args, Modes, IMD, AditiInfo, Code)
+			Args, Modes, IMD, Reuse, Unique, AditiInfo, Code)
 	;
 		{ Uni = deconstruct(Var, ConsId, Args, Modes, _CanFail) },
 		( { CodeModel = model_det } ->
 			unify_gen__generate_det_deconstruction(Var, ConsId,
-				Args, Modes, IMD, Code)
+				Args, Modes, GoalInfo, Code)
 		;
 			unify_gen__generate_semi_deconstruction(Var, ConsId,
-				Args, Modes, IMD, Code)
+				Args, Modes, GoalInfo, Code)
 		)
 	;
 		{ Uni = simple_test(Var1, Var2) },
@@ -265,97 +268,64 @@
 	% create a term, and a series of [optional] assignments to
 	% instantiate the arguments of that term.
 
-:- pred unify_gen__generate_construction(prog_var, cons_id,
-	list(prog_var), list(uni_mode), instmap_delta, maybe(rl_exprn_id),
-	code_tree, code_info, code_info).
-:- mode unify_gen__generate_construction(in, in, in, in, in, in, out, in, out)
-	is det.
+:- pred unify_gen__generate_construction(prog_var, cons_id, list(prog_var),
+	list(uni_mode), instmap_delta, maybe(cell_to_reuse), cell_is_unique,
+	maybe(rl_exprn_id), code_tree, code_info, code_info).
+:- mode unify_gen__generate_construction(in, in, in, in, in, in, in, in,
+	out, in, out) is det.
 
 unify_gen__generate_construction(Var, Cons, Args, Modes,
-		InstMapDelta, AditiInfo, Code) -->
+		InstMapDelta, CellToReuse, CellIsUnique, AditiInfo, Code) -->
 	code_info__cons_id_to_tag(Var, Cons, Tag),
-	unify_gen__generate_construction_2(Tag, Var, Args,
-		Modes, InstMapDelta, AditiInfo, Code).
+	unify_gen__generate_construction_2(Tag, Var, Args, Modes,
+		InstMapDelta, CellToReuse, CellIsUnique, AditiInfo, Code).
 
-:- pred unify_gen__generate_construction_2(cons_tag, prog_var, list(prog_var),
-	list(uni_mode), instmap_delta, maybe(rl_exprn_id),
-	code_tree, code_info, code_info).
-:- mode unify_gen__generate_construction_2(in, in, in, in, in, in, out,
-	in, out) is det.
+:- pred unify_gen__generate_construction_2(cons_tag, prog_var, 
+	list(prog_var), list(uni_mode), instmap_delta, maybe(cell_to_reuse),
+	cell_is_unique, maybe(rl_exprn_id), code_tree, code_info, code_info).
+:- mode unify_gen__generate_construction_2(in, in, in, in, in, in, in, in,
+	out, in, out) is det.
 
 unify_gen__generate_construction_2(string_constant(String),
-		Var, _Args, _Modes, _IMDelta, _, Code) -->
+		Var, _Args, _Modes, _IMDelta, _, _, _, Code) -->
 	unify_gen__cache_unification(Var, const(string_const(String)), Code).
 unify_gen__generate_construction_2(int_constant(Int),
-		Var, _Args, _Modes, _IMDelta, _, Code) -->
+		Var, _Args, _Modes, _IMDelta, _, _, _, Code) -->
 	unify_gen__cache_unification(Var, const(int_const(Int)), Code).
 unify_gen__generate_construction_2(float_constant(Float),
-		Var, _Args, _Modes, _IMDelta, _, Code) -->
+		Var, _Args, _Modes, _IMDelta, _, _, _, Code) -->
 	unify_gen__cache_unification(Var, const(float_const(Float)), Code).
 unify_gen__generate_construction_2(no_tag, Var, Args, Modes,
-		IMDelta, _, Code) -->
+		IMDelta, _, _, _, Code) -->
 	( { Args = [Arg], Modes = [Mode] } ->
 		code_info__variable_type(Arg, Type),
+		{ set__init(NonLocals) },
 		unify_gen__generate_sub_unify(ref(Var), ref(Arg),
-			Mode, Type, IMDelta, Code)
+			Mode, Type, no, NonLocals, IMDelta, Code)
 	;
 		{ error(
 		"unify_gen__generate_construction_2: no_tag: arity != 1") }
 	).
 unify_gen__generate_construction_2(unshared_tag(UnsharedTag),
-		Var, Args, Modes, IMDelta, _, Code) -->
-	code_info__get_module_info(ModuleInfo),
-	code_info__get_inst_table(InstTable),
-	code_info__get_instmap(InstMap0),
-	{ instmap__apply_instmap_delta(InstMap0, IMDelta, InstMap) },
-	code_info__get_next_cell_number(CellNo),
-	unify_gen__var_types(Args, ArgTypes),
-	{ unify_gen__generate_cons_args(Args, ArgTypes, Modes, InstMap0,
-		InstMap, InstTable, ModuleInfo, RVals) },
-	code_info__variable_type(Var, VarType),
-	{ unify_gen__var_type_msg(VarType, VarTypeMsg) },
-	% XXX Later we will need to worry about
-	% whether the cell must be unique or not.
-	{ Reuse = no },
-	{ Expr = create(UnsharedTag, RVals, uniform(no), can_be_either,
-		CellNo, VarTypeMsg, Reuse) },
-	code_info__cache_expression(Var, Expr),
-	unify_gen__aliased_vars_set_location(Args, ArgTypes, Modes,
-		InstMap0, InstMap, InstTable, ModuleInfo, Var, UnsharedTag,
-		0, Code0),
-	unify_gen__maybe_place_refs(Var, Code1),
-	{ Code = tree(Code0, Code1) }.
+		Var, Args, Modes, InstMapDelta, MaybeCellToReuse, CellIsUnique,
+		_, Code) -->
+	{ RemoteTag = no },
+	unify_gen__generate_tagged_cell(UnsharedTag, RemoteTag, Var, Args,
+		Modes, MaybeCellToReuse, CellIsUnique, InstMapDelta, Code).
 unify_gen__generate_construction_2(shared_remote_tag(Bits0, Num0),
-		Var, Args, Modes, IMDelta, _, Code) -->
-	code_info__get_module_info(ModuleInfo),
-	code_info__get_inst_table(InstTable),
-	code_info__get_instmap(InstMap0),
-	{ instmap__apply_instmap_delta(InstMap0, IMDelta, InstMap) },
-	code_info__get_next_cell_number(CellNo),
-	unify_gen__var_types(Args, ArgTypes),
-	{ unify_gen__generate_cons_args(Args, ArgTypes, Modes, InstMap0,
-		InstMap, InstTable, ModuleInfo, RVals0) },
-		% the first field holds the secondary tag
-	{ RVals = [yes(const(int_const(Num0))) | RVals0] },
-	code_info__variable_type(Var, VarType),
-	{ unify_gen__var_type_msg(VarType, VarTypeMsg) },
-	% XXX Later we will need to worry about
-	% whether the cell must be unique or not.
-	{ Reuse = no },
-	{ Expr = create(Bits0, RVals, uniform(no), can_be_either,
-		CellNo, VarTypeMsg, Reuse) },
-	code_info__cache_expression(Var, Expr),
-	unify_gen__aliased_vars_set_location(Args, ArgTypes, Modes, InstMap0,
-		InstMap, InstTable, ModuleInfo, Var, Bits0, 1, Code0),
-	unify_gen__maybe_place_refs(Var, Code1),
-	{ Code = tree(Code0, Code1) }.
+		Var, Args, Modes, InstMapDelta, MaybeCellToReuse, CellIsUnique,
+		_, Code) -->
+	{ RemoteTag = yes(Num0) },
+	unify_gen__generate_tagged_cell(Bits0, RemoteTag, Var, Args, Modes,
+		MaybeCellToReuse, CellIsUnique, InstMapDelta, Code).
 unify_gen__generate_construction_2(shared_local_tag(Bits1, Num1),
-		Var, _Args, _Modes, _IMDelta, _, Code) -->
+		Var, _Args, _Modes, _IMDelta, _, _, _, Code) -->
 	unify_gen__cache_unification(Var, 
 		mkword(Bits1, unop(mkbody, const(int_const(Num1)))),
 		Code).
 unify_gen__generate_construction_2(type_ctor_info_constant(ModuleName,
-		TypeName, TypeArity), Var, Args, _Modes, _IMDelta, _, Code) -->
+		TypeName, TypeArity), Var, Args, _Modes, _IMDelta,
+		_, _, _, Code) -->
 	( { Args = [] } ->
 		[]
 	;
@@ -363,8 +333,9 @@
 	),
 	unify_gen__cache_unification(Var, const(data_addr_const(data_addr(
 		ModuleName, type_ctor(info, TypeName, TypeArity)))), Code).
-unify_gen__generate_construction_2(base_typeclass_info_constant(ModuleName,
-		ClassId, Instance), Var, Args, _Modes, _IMDelta, _, Code) -->
+unify_gen__generate_construction_2(
+		base_typeclass_info_constant(ModuleName, ClassId, Instance),
+		Var, Args, _Modes, _IMDelta, _, _, _, Code) -->
 	( { Args = [] } ->
 		[]
 	;
@@ -374,7 +345,7 @@
 		ModuleName, base_typeclass_info(ClassId, Instance)))),
 		Code).
 unify_gen__generate_construction_2(tabling_pointer_constant(PredId, ProcId),
-		Var, Args, _Modes, _IMDelta, _, Code) -->
+		Var, Args, _Modes, _IMDelta, _, _, _, Code) -->
 	( { Args = [] } ->
 		[]
 	;
@@ -387,7 +358,7 @@
 	unify_gen__cache_unification(Var, const(data_addr_const(DataAddr)),
 		Code).
 unify_gen__generate_construction_2(code_addr_constant(PredId, ProcId),
-		Var, Args, _Modes, _IMDelta, _, Code) -->
+		Var, Args, _Modes, _IMDelta, _, _, _, Code) -->
 	( { Args = [] } ->
 		[]
 	;
@@ -399,7 +370,7 @@
 		Code).
 unify_gen__generate_construction_2(
 		pred_closure_tag(PredId, ProcId, EvalMethod),
-		Var, Args, Modes, IMDelta, _AditiInfo, Code) -->
+		Var, Args, Modes, IMDelta, _, _, _AditiInfo, Code) -->
 	% This code constructs or extends a closure.
 	% The structure of closures is defined in runtime/mercury_ho_call.h.
 
@@ -554,6 +525,8 @@
 			ClosureLayoutArgTypes, CNum0, CNum) },
 		code_info__set_cell_count(CNum),
 		code_info__get_next_cell_number(ClosureLayoutCellNo),
+		
+		% We currently don't reuse higher-order terms.
 		{ Reuse = no },
 		{ ClosureLayout = create(0, ClosureLayoutMaybeRvals,
 			ClosureLayoutArgTypes, must_be_static,
@@ -661,17 +634,92 @@
 	),
 	unify_gen__generate_pred_args(Vars, ArgInfos, Rvals).
 
+%---------------------------------------------------------------------------%
+
+:- pred unify_gen__generate_tagged_cell(tag_bits, maybe(int), prog_var,
+	list(prog_var), list(uni_mode), maybe(cell_to_reuse), cell_is_unique,
+	instmap_delta, code_tree, code_info, code_info).
+:- mode unify_gen__generate_tagged_cell(in, in, in, in, in, in, in, in,
+	out, in, out) is det.
+
+unify_gen__generate_tagged_cell(Ptag, MaybeStag, Var, Args, Modes,
+		MaybeCellToReuse, CellIsUnique, InstMapDelta, Code) -->
+	code_info__get_module_info(ModuleInfo),
+	code_info__get_inst_table(InstTable),
+	code_info__get_next_cell_number(CellNo),
+	unify_gen__var_types(Args, ArgTypes),
+	code_info__get_instmap(InstMapBefore),
+	{ instmap__apply_instmap_delta(InstMapBefore, InstMapDelta,
+		InstMapAfter) },
+	( { MaybeCellToReuse = yes(cell_to_reuse(ReuseVar, _, ReuseArgs)) } ->
+		{ FieldsToSet = some_fields(ReuseArgs) },
+		{ unify_gen__generate_cons_args(Args, ArgTypes, Modes,
+			FieldsToSet, InstMapBefore, InstMapAfter,
+			InstTable, ModuleInfo, RVals0) },
+
+		{ ReuseRval = yes(var(ReuseVar)) },
+
+		% For now, structure_reuse.m ensures that the tags
+		% of the reused cells do not need updating.
+		{ MaybeStag = yes(_) ->
+			RVals = [no | RVals0],
+			ArgOffset = 1
+		;
+			RVals = RVals0,
+			ArgOffset = 0
+		}
+	;
+		{ FieldsToSet = all_fields },
+		{ unify_gen__generate_cons_args(Args, ArgTypes, Modes,
+			FieldsToSet, InstMapBefore, InstMapAfter,
+			InstTable, ModuleInfo, RVals0) },
+
+		{ ReuseRval = no },
+
+		% The first field holds the secondary tag.
+		{ MaybeStag = yes(Stag) ->
+			RVals = [yes(const(int_const(Stag))) | RVals0],
+			ArgOffset = 1
+		;
+			RVals = RVals0,
+			ArgOffset = 0
+		}
+	),
+	code_info__variable_type(Var, VarType),
+	{ unify_gen__var_type_msg(VarType, VarTypeMsg) },
+	(
+		{ CellIsUnique = cell_is_unique },
+		{ StatOrDyn = must_be_dynamic }
+	;
+		{ CellIsUnique = cell_is_shared },
+		{ StatOrDyn = can_be_either }
+	),
+	{ Expr = create(Ptag, RVals, uniform(no), StatOrDyn, CellNo,
+			VarTypeMsg, ReuseRval) },
+	code_info__cache_expression(Var, Expr),
+	unify_gen__aliased_vars_set_location(Args, ArgTypes, Modes,
+		InstMapBefore, InstMapAfter, InstTable,
+		ModuleInfo, Var, Ptag, ArgOffset, Code0),
+	unify_gen__maybe_place_refs(Var, Code1),
+	{ Code = tree(Code0, Code1) }.
+
+:- type fields_to_set
+	--->	some_fields(list(bool))	% fill in the `yes's
+	;	all_fields
+	.
+
 :- pred unify_gen__generate_cons_args(list(prog_var), list(type),
-	list(uni_mode), instmap, instmap, inst_table, module_info,
-	list(maybe(rval))).
-:- mode unify_gen__generate_cons_args(in, in, in, in, in, in, in, out) is det.
+	list(uni_mode), fields_to_set, instmap, instmap, inst_table,
+	module_info, list(maybe(rval))).
+:- mode unify_gen__generate_cons_args(in, in, in, in, in, in,
+	in, in, out) is det.
 
-unify_gen__generate_cons_args(Vars, Types, Modes, InstMapBefore, InstMapAfter,
-		InstTable, ModuleInfo, Args) :-
+unify_gen__generate_cons_args(Vars, Types, Modes, FieldsToSet,
+		InstMapBefore, InstMapAfter, InstTable, ModuleInfo, Args) :-
 	(
 		unify_gen__generate_cons_args_2(Vars, Types, Modes,
-				InstMapBefore, InstMapAfter, InstTable,
-				ModuleInfo, Args0)
+			FieldsToSet, InstMapBefore, InstMapAfter, InstTable,
+			ModuleInfo, Args0)
 	->
 		Args = Args0
 	;
@@ -685,17 +733,29 @@
 	% generate an assignment to that field.
 
 :- pred unify_gen__generate_cons_args_2(list(prog_var), list(type),
-	list(uni_mode), instmap, instmap, inst_table, module_info,
-	list(maybe(rval))).
-:- mode unify_gen__generate_cons_args_2(in, in, in, in, in, in, in, out)
-		is semidet.
-
-unify_gen__generate_cons_args_2([], [], [], _, _, _, _, []).
+	list(uni_mode), fields_to_set, instmap, instmap, inst_table,
+	module_info, list(maybe(rval))).
+:- mode unify_gen__generate_cons_args_2(in, in, in, in,
+	in, in, in, in, out) is semidet.
+
+unify_gen__generate_cons_args_2([], [], [], FieldsToSet, _, _, _, _, []) :-
+	( FieldsToSet = all_fields
+	; FieldsToSet = some_fields([])
+	).
 unify_gen__generate_cons_args_2([Var|Vars], [Type|Types], [UniMode|UniModes],
-		InstMapBefore, InstMapAfter, InstTable, ModuleInfo,
-		[Arg|RVals]) :-
+		FieldsToSet0, InstMapBefore, InstMapAfter, InstTable,
+		ModuleInfo, [Arg|RVals]) :-
+	(
+		FieldsToSet0 = all_fields,
+		FieldsToSet = all_fields,
+		SetField = yes
+	;
+		FieldsToSet0 = some_fields([SetField | SetFields]),
+		FieldsToSet = some_fields(SetFields)
+	),
 	UniMode = ((_LI - RI) -> (_LF - RF)),
 	(
+		SetField = yes,
 		insts_to_arg_mode(InstTable, ModuleInfo, RI, InstMapBefore,
 				RF, InstMapAfter, Type, top_in)
 	->
@@ -703,8 +763,8 @@
 	;
 		Arg = no
 	),
-	unify_gen__generate_cons_args_2(Vars, Types, UniModes, InstMapBefore,
-		InstMapAfter, InstTable, ModuleInfo, RVals).
+	unify_gen__generate_cons_args_2(Vars, Types, UniModes, FieldsToSet,
+		InstMapBefore, InstMapAfter, InstTable, ModuleInfo, RVals).
 
 :- pred unify_gen__aliased_vars_set_location(list(prog_var), list(type),
 		list(uni_mode), instmap, instmap, inst_table, module_info,
@@ -810,13 +870,16 @@
 	% assignment unifications are cached.
 
 :- pred unify_gen__generate_det_deconstruction(prog_var, cons_id,
-	list(prog_var), list(uni_mode), instmap_delta, code_tree,
+	list(prog_var), list(uni_mode), hlds_goal_info, code_tree,
 	code_info, code_info).
 :- mode unify_gen__generate_det_deconstruction(in, in, in, in, in, out,
 	in, out) is det.
 
-unify_gen__generate_det_deconstruction(Var, Cons, Args, Modes, IMDelta,
+unify_gen__generate_det_deconstruction(Var, Cons, Args, Modes, GoalInfo,
 		Code) -->
+	{ goal_info_get_instmap_delta(GoalInfo, IMDelta) },
+	{ goal_info_get_code_gen_nonlocals(GoalInfo, NonLocals) },
+
 	code_info__cons_id_to_tag(Var, Cons, Tag),
 	% For constants, if the deconstruction is det, then we already know
 	% the value of the constant, so Code = empty.
@@ -849,31 +912,57 @@
 		( { Args = [Arg], Modes = [Mode] } ->
 			code_info__variable_type(Arg, Type),
 			unify_gen__generate_sub_unify(ref(Var), ref(Arg),
-				Mode, Type, IMDelta, Code)
+				Mode, Type, no, NonLocals, IMDelta, Code)
 		;
 			{ error("unify_gen__generate_det_deconstruction: no_tag: arity != 1") }
 		)
 	;
 		{ Tag = unshared_tag(UnsharedTag) },
 		{ Rval = var(Var) },
+
+		unify_gen__must_flush_deconstruct_args(Var, Flush),
 		{ unify_gen__make_fields_and_argvars(Args, Rval, 0,
 			UnsharedTag, Fields, ArgVars) },
 		unify_gen__var_types(Args, ArgTypes),
 		unify_gen__generate_unify_args(Fields, ArgVars,
-			Modes, ArgTypes, IMDelta, Code)
+			Modes, ArgTypes, Flush, NonLocals, IMDelta, Code)
 	;
 		{ Tag = shared_remote_tag(Bits0, _Num0) },
 		{ Rval = var(Var) },
 		{ unify_gen__make_fields_and_argvars(Args, Rval, 1,
 			Bits0, Fields, ArgVars) },
 		unify_gen__var_types(Args, ArgTypes),
+		unify_gen__must_flush_deconstruct_args(Var, Flush),
 		unify_gen__generate_unify_args(Fields, ArgVars,
-			Modes, ArgTypes, IMDelta, Code)
+			Modes, ArgTypes, Flush, NonLocals, IMDelta, Code)
 	;
 		{ Tag = shared_local_tag(_Bits1, _Num1) },
 		{ Code = empty } % if this is det, then nothing happens
 	).
 
+	% The arguments of deconstructions of unique variables must
+	% be flushed so that they are evaluated before any destructive
+	% update or compile-time garbage collection of the cell.
+:- pred unify_gen__must_flush_deconstruct_args(prog_var, bool,
+		code_info, code_info).
+:- mode unify_gen__must_flush_deconstruct_args(in, out, in, out) is det.
+
+unify_gen__must_flush_deconstruct_args(Var, Flush) -->
+	code_info__get_instmap(InstMap),
+	code_info__get_inst_table(InstTable),
+	code_info__get_module_info(ModuleInfo),
+	{ instmap__lookup_var(InstMap, Var, VarInst) },
+	{ inst_expand(InstMap, InstTable, ModuleInfo, VarInst, VarInst1) },
+	(
+		{ VarInst1 = bound(unique, _)
+		; VarInst1 = ground(unique, _)
+		}
+	->
+		{ Flush = yes }
+	;
+		{ Flush = no }
+	).
+
 %---------------------------------------------------------------------------%
 
 	% Generate a semideterministic deconstruction.
@@ -881,12 +970,12 @@
 	% followed by a deterministic deconstruction.
 
 :- pred unify_gen__generate_semi_deconstruction(prog_var, cons_id,
-	list(prog_var), list(uni_mode), instmap_delta, code_tree,
+	list(prog_var), list(uni_mode), hlds_goal_info, code_tree,
 	code_info, code_info).
 :- mode unify_gen__generate_semi_deconstruction(in, in, in, in, in, out,
 	in, out) is det.
 
-unify_gen__generate_semi_deconstruction(Var, Tag, Args, Modes, IMDelta,
+unify_gen__generate_semi_deconstruction(Var, Tag, Args, Modes, GoalInfo,
 			Code) -->
 	unify_gen__generate_tag_test(Var, Tag, branch_on_success,
 		SuccLab, TagTestCode),
@@ -894,7 +983,7 @@
 	code_info__generate_failure(FailCode),
 	code_info__reset_to_position(AfterUnify),
 	unify_gen__generate_det_deconstruction(Var, Tag, Args, Modes,
-		IMDelta, DeconsCode),
+		GoalInfo, DeconsCode),
 	{ SuccessLabelCode = node([
 		label(SuccLab) - ""
 	]) },
@@ -908,32 +997,37 @@
 %---------------------------------------------------------------------------%
 
 	% Generate code to perform a list of deterministic subunifications
-	% for the arguments of a construction.
+	% for the arguments of a deconstruction.
 
 :- pred unify_gen__generate_unify_args(list(uni_val), list(uni_val),
-			list(uni_mode), list(type), instmap_delta, code_tree,
-			code_info, code_info).
-:- mode unify_gen__generate_unify_args(in, in, in, in, in, out,
+			list(uni_mode), list(type), bool, set(prog_var),
+			instmap_delta, code_tree, code_info, code_info).
+:- mode unify_gen__generate_unify_args(in, in, in, in, in, in, in, out,
 			in, out) is det.
 
-unify_gen__generate_unify_args(Ls, Rs, Ms, Ts, IMDelta, Code) -->
-	( unify_gen__generate_unify_args_2(Ls, Rs, Ms, Ts, IMDelta, Code0) ->
+unify_gen__generate_unify_args(Ls, Rs, Ms, Ts, F, Ns, IMDelta, Code) -->
+	(
+		unify_gen__generate_unify_args_2(Ls, Rs, Ms,
+			Ts, F, Ns, IMDelta, Code0)
+	->
 		{ Code = Code0 }
 	;
 		{ error("unify_gen__generate_unify_args: length mismatch") }
 	).
 
 :- pred unify_gen__generate_unify_args_2(list(uni_val), list(uni_val),
-			list(uni_mode), list(type), instmap_delta, code_tree,
-			code_info, code_info).
-:- mode unify_gen__generate_unify_args_2(in, in, in, in, in, out, in, out)
-	is semidet.
+			list(uni_mode), list(type), bool, set(prog_var),
+			instmap_delta, code_tree, code_info, code_info).
+:- mode unify_gen__generate_unify_args_2(in, in, in, in, in, in, in, out,
+			in, out) is semidet.
 
-unify_gen__generate_unify_args_2([], [], [], [], _, empty) --> [].
-unify_gen__generate_unify_args_2([L|Ls], [R|Rs], [M|Ms], [T|Ts], IMDelta,
-			Code) -->
-	unify_gen__generate_sub_unify(L, R, M, T, IMDelta, CodeA),
-	unify_gen__generate_unify_args_2(Ls, Rs, Ms, Ts, IMDelta, CodeB),
+unify_gen__generate_unify_args_2([], [], [], [], _, _, _, empty) --> [].
+unify_gen__generate_unify_args_2([L|Ls], [R|Rs], [M|Ms], [T|Ts], Flush,
+			NonLocals, IMDelta, Code) -->
+	unify_gen__generate_sub_unify(L, R, M, T, Flush, NonLocals,
+		IMDelta, CodeA),
+	unify_gen__generate_unify_args_2(Ls, Rs, Ms, Ts,
+		Flush, NonLocals, IMDelta, CodeB),
 	{ Code = tree(CodeA, CodeB) }.
 
 %---------------------------------------------------------------------------%
@@ -941,10 +1035,12 @@
 	% Generate a subunification between two [field|variable].
 
 :- pred unify_gen__generate_sub_unify(uni_val, uni_val, uni_mode, type,
-			instmap_delta, code_tree, code_info, code_info).
-:- mode unify_gen__generate_sub_unify(in, in, in, in, in, out, in, out) is det.
+	bool, set(prog_var), instmap_delta, code_tree, code_info, code_info).
+:- mode unify_gen__generate_sub_unify(in, in, in, in, in, in,
+	in, out, in, out) is det.
 
-unify_gen__generate_sub_unify(L, R, Mode, Type, IMDelta, Code) -->
+unify_gen__generate_sub_unify(L, R, Mode, Type, Flush, NonLocals,
+		IMDelta, Code) -->
 	{ Mode = ((LI - RI) -> (LF - RF)) },
 	code_info__get_module_info(ModuleInfo),
 	code_info__get_inst_table(IT),
@@ -968,13 +1064,13 @@
 		{ LeftMode = top_in },
 		{ RightMode = top_out ; RightMode = ref_in }
 	->
-		unify_gen__generate_sub_assign(R, L, Code)
+		unify_gen__generate_sub_assign(R, L, Flush, NonLocals, Code)
 	;
 			% Input - Output== assignment <-
 		{ LeftMode = top_out ; LeftMode = ref_in },
 		{ RightMode = top_in }
 	->
-		unify_gen__generate_sub_assign(L, R, Code)
+		unify_gen__generate_sub_assign(L, R, Flush, NonLocals, Code)
 	;
 		{ LeftMode = top_unused },
 		{ RightMode = top_unused }
@@ -991,15 +1087,15 @@
 
 %---------------------------------------------------------------------------%
 
-:- pred unify_gen__generate_sub_assign(uni_val, uni_val, code_tree,
-							code_info, code_info).
-:- mode unify_gen__generate_sub_assign(in, in, out, in, out) is det.
+:- pred unify_gen__generate_sub_assign(uni_val, uni_val, bool,
+		set(prog_var), code_tree, code_info, code_info).
+:- mode unify_gen__generate_sub_assign(in, in, in, in, out, in, out) is det.
 
 	% Assignment between two lvalues - cannot cache [yet]
 	% so generate immediate code
 	% If the destination of the assignment contains any vars,
 	% we need to materialize those before we can do the assignment.
-unify_gen__generate_sub_assign(lval(Lval0), lval(Rval), Code) -->
+unify_gen__generate_sub_assign(lval(Lval0), lval(Rval), _, _, Code) -->
 	code_info__materialize_vars_in_rval(lval(Lval0), NewLval,
 		MaterializeCode),
 	(
@@ -1013,7 +1109,7 @@
 	).
 	% assignment from a variable to an lvalue - cannot cache
 	% so generate immediately
-unify_gen__generate_sub_assign(lval(Lval0), ref(Var), Code) -->
+unify_gen__generate_sub_assign(lval(Lval0), ref(Var), _, _, Code) -->
 	code_info__produce_variable(Var, SourceCode, Source),
 	code_info__materialize_vars_in_rval(lval(Lval0), NewLval,
 		MaterializeCode),
@@ -1030,22 +1126,38 @@
 		{ error("unify_gen__generate_sub_assign: lval vanished with ref") }
 	).
 	% assignment to a variable, so cache it.
-unify_gen__generate_sub_assign(ref(Var), lval(Rval), Code) -->
+unify_gen__generate_sub_assign(ref(Var), lval(Rval),
+		Flush, NonLocals, Code) -->
 	(
 		code_info__variable_is_forward_live(Var)
 	->
 		code_info__cache_expression(Var, lval(Rval)),
-		code_info__produce_variable_in_references(Var, Code)
+		( { Flush = yes, set__member(Var, NonLocals) } ->
+			code_info__produce_variable_in_reg_or_stack(Var,
+				ProdCode, _)
+		;
+			{ ProdCode = empty }
+		),
+		code_info__produce_variable_in_references(Var, RefCode),
+		{ Code = tree(ProdCode, RefCode) }
 	;
 		{ Code = empty }
 	).
 	% assignment to a variable, so cache it.
-unify_gen__generate_sub_assign(ref(Lvar), ref(Rvar), Code) -->
+unify_gen__generate_sub_assign(ref(Lvar), ref(Rvar),
+			Flush, NonLocals, Code) -->
 	(
 		code_info__variable_is_forward_live(Lvar)
 	->
 		code_info__cache_expression(Lvar, var(Rvar)),
-		code_info__produce_variable_in_references(Lvar, Code)
+		( { Flush = yes, set__member(Lvar, NonLocals) } ->
+			code_info__produce_variable_in_reg_or_stack(Lvar,
+				ProdCode, _)
+		;
+			{ ProdCode = empty }
+		),
+		code_info__produce_variable_in_references(Lvar, RefCode),
+		{ Code = tree(ProdCode, RefCode) }
 	;
 		{ Code = empty }
 	).

--------------------------------------------------------------------------
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