[m-dev.] for review: fix inter-module inlining heuristic

Simon Taylor stayl at cs.mu.OZ.AU
Thu Oct 14 12:45:44 AEST 1999



Estimated hours taken: 1.5

Fix problems with the inter-module inlining heuristics.
The changes to run polymorphism.m before mode analysis caused
all exported predicates to be placed in the `.opt' files, regardless
of their size. This resulted in compilation of compiler/mercury_compile.m
with --intermodule-optimization to run out of memory.

compiler/intermod.m:
	Don't assume that the clauses have been copied to the procedures
	when computing goal sizes.

	Use --higher-order-size-limit rather than placing all predicates
	with higher-order arguments in the `.opt' file.

compiler/inlining.m:
	Add inlining__is_simple_clause_list, similar to
	inlining__is_simple_goal.

compiler/goal_util.m:
	Add clause_list_size, similar to goals_size.

tests/term/*.trans_opt_exp:
	Undo changes to the expected output caused by this bug.



Index: compiler/goal_util.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/goal_util.m,v
retrieving revision 1.56
diff -u -u -r1.56 goal_util.m
--- goal_util.m	1999/09/30 23:08:20	1.56
+++ goal_util.m	1999/10/08 05:51:19
@@ -114,6 +114,10 @@
 :- pred goals_size(list(hlds_goal), int).
 :- mode goals_size(in, out) is det.
 
+	% Return an indication of the size of the list of clauses.
+:- pred clause_list_size(list(clause), int).
+:- mode clause_list_size(in, out) is det.
+
 	% Test whether the goal calls the given procedure.
 :- pred goal_calls(hlds_goal, pred_proc_id).
 :- mode goal_calls(in, in) is semidet.
@@ -670,6 +674,21 @@
 	goal_size(Goal, Size1),
 	goals_size(Goals, Size2),
 	Size is Size1 + Size2.
+
+clause_list_size(Clauses, GoalSize) :-
+	GetClauseSize =
+		(pred(Clause::in, Size0::in, Size::out) is det :-
+			Clause = clause(_, ClauseGoal, _),
+			goal_size(ClauseGoal, ClauseSize),
+			Size = Size0 + ClauseSize
+		),
+	list__foldl(GetClauseSize, Clauses, 0, GoalSize0),
+	( Clauses = [_] ->
+		GoalSize = GoalSize0
+	;
+		% Add one for the disjunction.
+		GoalSize = GoalSize0 + 1
+	).
 
 :- pred cases_size(list(case), int).
 :- mode cases_size(in, out) is det.
Index: compiler/inlining.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/inlining.m,v
retrieving revision 1.82
diff -u -u -r1.82 inlining.m
--- inlining.m	1999/07/13 08:53:00	1.82
+++ inlining.m	1999/10/08 05:44:27
@@ -88,6 +88,9 @@
 :- pred inlining(module_info, module_info, io__state, io__state).
 :- mode inlining(in, out, di, uo) is det.
 
+:- pred inlining__is_simple_clause_list(list(clause), int).
+:- mode inlining__is_simple_clause_list(in, in) is semidet.
+
 :- pred inlining__is_simple_goal(hlds_goal, int).
 :- mode inlining__is_simple_goal(in, in) is semidet.
 
@@ -283,6 +286,22 @@
 
 	% this heuristic is used for both local and intermodule inlining
 
+inlining__is_simple_clause_list(Clauses, SimpleThreshold) :-
+	clause_list_size(Clauses, Size),
+	(
+		Size < SimpleThreshold
+	;
+		Clauses = [clause(_, Goal, _)],
+		Size < SimpleThreshold * 3,
+		%
+		% For flat goals, we are more likely to be able to
+		% optimize stuff away, so we use a higher threshold.
+		% XXX this should be a separate option, we shouldn't
+		% hardcode the number `3' (which is just a guess).
+		%
+		inlining__is_flat_simple_goal(Goal)
+	).
+		
 inlining__is_simple_goal(CalledGoal, SimpleThreshold) :-
 	goal_size(CalledGoal, Size),
 	(
Index: compiler/intermod.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/intermod.m,v
retrieving revision 1.69
diff -u -u -r1.69 intermod.m
--- intermod.m	1999/09/12 04:26:42	1.69
+++ intermod.m	1999/10/12 01:24:31
@@ -99,8 +99,11 @@
 		globals__io_lookup_int_option(
 			intermod_inline_simple_threshold, Threshold),
 		globals__io_lookup_bool_option(deforestation, Deforestation),
+		globals__io_lookup_int_option(higher_order_size_limit,
+			HigherOrderSizeLimit),
 		{ intermod__gather_preds(PredIds, yes, Threshold,
-			Deforestation, IntermodInfo0, IntermodInfo1) },
+			HigherOrderSizeLimit, Deforestation,
+			IntermodInfo0, IntermodInfo1) },
 		{ intermod__gather_abstract_exported_types(IntermodInfo1,
 				IntermodInfo2) },
 		{ intermod_info_get_pred_decls(PredDeclsSet,
@@ -162,11 +165,11 @@
 	% Predicates to gather stuff to output to .opt file.
 
 :- pred intermod__gather_preds(list(pred_id)::in, bool::in, int::in,
-		bool::in, intermod_info::in, intermod_info::out) is det.
+	int::in, bool::in, intermod_info::in, intermod_info::out) is det.
 
-intermod__gather_preds([], _CollectTypes, _, _) --> [].
+intermod__gather_preds([], _CollectTypes, _, _, _) --> [].
 intermod__gather_preds([PredId | PredIds], CollectTypes,
-		InlineThreshold, Deforestation) -->
+		InlineThreshold, HigherOrderSizeLimit, Deforestation) -->
 	intermod_info_get_module_info(ModuleInfo0),
 	{ module_info_preds(ModuleInfo0, PredTable0) },
 	{ map__lookup(PredTable0, PredId, PredInfo0) },
@@ -174,8 +177,8 @@
 	{ TypeSpecInfo = type_spec_info(_, TypeSpecForcePreds, _, _) },
 	(
 		{ intermod__should_be_processed(PredId, PredInfo0,
-				TypeSpecForcePreds, InlineThreshold,
-				Deforestation, ModuleInfo0) }
+			TypeSpecForcePreds, InlineThreshold,
+			HigherOrderSizeLimit, Deforestation, ModuleInfo0) }
 	->
 		=(IntermodInfo0),
 		{ pred_info_clauses_info(PredInfo0, ClausesInfo0) },
@@ -222,15 +225,16 @@
 		[]
 	),
 	intermod__gather_preds(PredIds, CollectTypes,
-		InlineThreshold, Deforestation).
+		InlineThreshold, HigherOrderSizeLimit, Deforestation).
 
 
 :- pred intermod__should_be_processed(pred_id::in, pred_info::in,
-		set(pred_id)::in, int::in, bool::in,
+		set(pred_id)::in, int::in, int::in, bool::in,
 		module_info::in) is semidet.
 
 intermod__should_be_processed(PredId, PredInfo, TypeSpecForcePreds,
-		InlineThreshold, Deforestation, ModuleInfo) :-
+		InlineThreshold, HigherOrderSizeLimit,
+		Deforestation, ModuleInfo) :-
 	%
 	% note: we can't include exported_to_submodules predicates in
 	% the `.opt' file, for reasons explained in the comments for
@@ -238,40 +242,45 @@
 	%
 	pred_info_is_exported(PredInfo),
 	(
+		pred_info_clauses_info(PredInfo, ClauseInfo),
+		clauses_info_clauses(ClauseInfo, Clauses),
+
 		pred_info_procids(PredInfo, [ProcId | _ProcIds]),
 		pred_info_procedures(PredInfo, Procs),
 		map__lookup(Procs, ProcId, ProcInfo),
-		proc_info_goal(ProcInfo, Goal),
-		(
-			% Don't export builtins since they will be
-			% recreated in the importing module anyway.
-			\+ code_util__compiler_generated(PredInfo),
-			\+ code_util__predinfo_is_builtin(PredInfo),
 
-			% These will be recreated in the importing module.
-			\+ set__member(PredId, TypeSpecForcePreds),
-			(
-				inlining__is_simple_goal(Goal, InlineThreshold),
-				pred_info_get_markers(PredInfo, Markers),
-				\+ check_marker(Markers, no_inline),
-				proc_info_eval_method(ProcInfo, eval_normal)
-			;
-				pred_info_requested_inlining(PredInfo)
-			;
-				has_ho_input(ModuleInfo, ProcInfo)
-			;
-				Deforestation = yes,
-				% Double the inline-threshold since
-				% goals we want to deforest will have at
-				% least two disjuncts. This allows one
-				% simple goal in each disjunct.  The
-				% disjunction adds one to the goal size,
-				% hence the `+1'.
-				DeforestThreshold is InlineThreshold * 2 + 1,
-				inlining__is_simple_goal(Goal,
-					DeforestThreshold),
-				goal_is_deforestable(PredId, Goal)
-			)
+		% Don't export builtins since they will be
+		% recreated in the importing module anyway.
+		\+ code_util__compiler_generated(PredInfo),
+		\+ code_util__predinfo_is_builtin(PredInfo),
+
+		% These will be recreated in the importing module.
+		\+ set__member(PredId, TypeSpecForcePreds),
+
+		(
+			inlining__is_simple_clause_list(Clauses,
+				InlineThreshold),
+			pred_info_get_markers(PredInfo, Markers),
+			\+ check_marker(Markers, no_inline),
+			proc_info_eval_method(ProcInfo, eval_normal)
+		;
+			pred_info_requested_inlining(PredInfo)
+		;
+			has_ho_input(ModuleInfo, ProcInfo),
+			clause_list_size(Clauses, GoalSize),
+			GoalSize =< HigherOrderSizeLimit
+		;
+			Deforestation = yes,
+			% Double the inline-threshold since
+			% goals we want to deforest will have at
+			% least two disjuncts. This allows one
+			% simple goal in each disjunct.  The
+			% disjunction adds one to the goal size,
+			% hence the `+1'.
+			DeforestThreshold is InlineThreshold * 2 + 1,
+			inlining__is_simple_clause_list(Clauses,
+				DeforestThreshold),
+			clause_list_is_deforestable(PredId, Clauses)
 		)
 	;
 		% assertions that are in the interface should always get
@@ -320,11 +329,26 @@
 
 	% Rough guess: a goal is deforestable if it contains a single
 	% top-level branched goal and is recursive.
-:- pred goal_is_deforestable(pred_id::in, hlds_goal::in) is semidet.
+:- pred clause_list_is_deforestable(pred_id::in, list(clause)::in) is semidet.
+
+clause_list_is_deforestable(PredId, Clauses)  :-
+	some [Clause1] (
+		list__member(Clause1, Clauses),
+		Clause1 = clause(_, Goal1, _),
+		goal_calls_pred_id(Goal1, PredId)
+	),
+	(
+		Clauses = [_, _ | _]
+	;
+		Clauses = [Clause2],
+		Clause2 = clause(_, Goal2, _),
+		goal_to_conj_list(Goal2, GoalList),
+		goal_contains_one_branched_goal(GoalList)
+	).
+
+:- pred goal_contains_one_branched_goal(list(hlds_goal)::in) is semidet.
 
-goal_is_deforestable(PredId, Goal)  :-
-	goal_calls_pred_id(Goal, PredId),
-	goal_to_conj_list(Goal, GoalList),
+goal_contains_one_branched_goal(GoalList) :-
 	goal_contains_one_branched_goal(GoalList, no).
 
 :- pred goal_contains_one_branched_goal(list(hlds_goal)::in,
@@ -1442,7 +1466,9 @@
 	globals__lookup_int_option(Globals, intermod_inline_simple_threshold, 
 			Threshold),
 	globals__lookup_bool_option(Globals, deforestation, Deforestation),
-	intermod__gather_preds(PredIds, yes, Threshold,
+	globals__lookup_int_option(Globals, higher_order_size_limit,
+		HigherOrderSizeLimit),
+	intermod__gather_preds(PredIds, yes, Threshold, HigherOrderSizeLimit,
 		Deforestation, Info0, Info1),
 	intermod__gather_abstract_exported_types(Info1, Info),
 	do_adjust_pred_import_status(Info, Module0, Module),
Index: tests/term/arit_exp.trans_opt_exp
===================================================================
RCS file: /home/mercury1/repository/tests/term/arit_exp.trans_opt_exp,v
retrieving revision 1.4
diff -u -u -r1.4 arit_exp.trans_opt_exp
--- arit_exp.trans_opt_exp	1999/06/30 17:13:48	1.4
+++ arit_exp.trans_opt_exp	1999/10/11 05:20:51
@@ -1,3 +1,2 @@
 :- module arit_exp.
 :- pragma termination_info(arit_exp:e((builtin:in)), finite(0, [no]), cannot_loop).
-:- pragma termination_info(arit_exp:f((builtin:in)), finite(0, [no]), cannot_loop).
Index: tests/term/associative.trans_opt_exp
===================================================================
RCS file: /home/mercury1/repository/tests/term/associative.trans_opt_exp,v
retrieving revision 1.6
diff -u -u -r1.6 associative.trans_opt_exp
--- associative.trans_opt_exp	1999/06/30 17:13:49	1.6
+++ associative.trans_opt_exp	1999/10/11 05:20:51
@@ -1,3 +1,2 @@
 :- module associative.
 :- pragma termination_info(associative:normal_form((builtin:in), (builtin:out)), finite(0, [yes, no]), can_loop).
-:- pragma termination_info(associative:rewrite((builtin:in), (builtin:out)), finite(0, [yes, no]), cannot_loop).
Index: tests/term/pl5_2_2.trans_opt_exp
===================================================================
RCS file: /home/mercury1/repository/tests/term/pl5_2_2.trans_opt_exp,v
retrieving revision 1.4
diff -u -u -r1.4 pl5_2_2.trans_opt_exp
--- pl5_2_2.trans_opt_exp	1999/06/30 17:13:50	1.4
+++ pl5_2_2.trans_opt_exp	1999/10/11 05:20:53
@@ -1,3 +1,2 @@
 :- module pl5_2_2.
 :- pragma termination_info(pl5_2_2:turing((builtin:in), (builtin:in), (builtin:in), (builtin:out)), infinite, can_loop).
-:- pragma termination_info(pl5_2_2:member((builtin:out), (builtin:in)), finite(-1, [no, no, yes]), cannot_loop).
Index: tests/term/vangelder.trans_opt_exp
===================================================================
RCS file: /home/mercury1/repository/tests/term/vangelder.trans_opt_exp,v
retrieving revision 1.4
diff -u -u -r1.4 vangelder.trans_opt_exp
--- vangelder.trans_opt_exp	1999/06/30 17:13:51	1.4
+++ vangelder.trans_opt_exp	1999/10/11 05:20:54
@@ -1,4 +1,2 @@
 :- module vangelder.
 :- pragma termination_info(vangelder:q((builtin:in), (builtin:in)), finite(0, [no, no]), can_loop).
-:- pragma termination_info(vangelder:p((builtin:in), (builtin:in)), finite(0, [no, no]), can_loop).
-:- pragma termination_info(vangelder:e((builtin:in), (builtin:in)), finite(0, [no, no]), cannot_loop).
--------------------------------------------------------------------------
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