[m-dev.] for review: Accumulator introduction

Fergus Henderson fjh at cs.mu.OZ.AU
Tue Jun 23 21:43:06 AEST 1998


On 23-Jun-1998, Peter David ROSS <petdr at cs.mu.OZ.AU> wrote:
> Support to allow the compiler to recognise and transform predicates 
> which can use accumulators (which makes the predicates tail recursive).
> 
> <directory>/<file>:
> 	<detailed description of changes>

You can delete that part of the template from the actual log message.

> compiler/mercury_compile.m:
>     Add the accumulator introduction pass after simplification.

This is ambiguous, since the simplification pass is done twice.
If you add a new module, or a new pass, you need to update
compiler/notes/compiler_design.html to document it's role.
That is a good place to document any constraints on the ordering
of the various passes, e.g. "the accumulator introduction pass
must come after ... because ... and must come before ... because ...".
(But you don't need to document the ordinary constraints that
apply to all optimization passes, e.g. that they need to come
after the semantic analysis/checking phases and before code generation.)

> compiler/options.m:
>     Add support for the option --introduce-accumulators

You need to also update doc/user_guide.texi to document that option.

> +mercury_compile__maybe_introduce_accumulators(HLDS0, Verbose, Stats, HLDS) -->
> +	globals__io_lookup_bool_option(introduce_accumulators, Optimize),
> +	( { Optimize = yes } ->
> +		maybe_write_string(Verbose,
> +				"% Introduce accumulators...\n"),
> +		maybe_flush_output(Verbose),
> +		{ accumulator__introduction(HLDS0, HLDS) },
> +		maybe_write_string(Verbose, "% done.\n"),

s/Introduce/Introducing/

Actually I suppose it might be more accurate to say
"Performing accumulator-introduction optimization..."
or "Attempting to introduce accumulators",
rather than "Introducing accumulators".

There should be no "\n" after the "..." and no "%" before the " done.\n".

> @@ -1772,6 +1775,8 @@
>  
>  	io__write_string("\t--optimize-higher-order\n"),
>  	io__write_string("\t\tEnable specialization higher-order predicates.\n"),

By the way, that should be "... specialization of higher-order ..."
                                               ^^
That one is not part of your change, of course, but you might as well fix
that at the same time.

> +	io__write_string("\t--introduce-accumulators\n"),
> +	io__write_string("\t\tEnable the introduction of accumulators.\n"),

A slightly more detailed description might be helpful here.

> New File: accumulator.m
> ===================================================================
> %-----------------------------------------------------------------------------%
> % Copyright (C) 1993-1998 The University of Melbourne.

Been working on it for a while, hey? ;-)

> % File:		accumulator.m
> % Main authors: petdr
> 
> % Identify predicates which can be converted from ordinary recursion
> % into accumulator recursion.  This normally leads to the new predicate
> % being tail recursive.

I'd like to see a lot more (and better) documentation here,
including (at least) an example of the kind of transformation that
the module performs.

Does the module just identify the predicates, or does it actually
transform them?

If the new predicate isn't tail recursive, is the transformation still applied?

Does the transformation apply to predicates, or to procedures?

> 	%
> 	% Holds all the information that could be needed by the
> 	% code.
> 	%
> :- type info
> 	--->	info(
> 			proc_id,
> 			proc_info,
> 			pred_id,
> 			pred_info,
> 			module_info
> 		).

I suggest you use a more informative name such as accumulator_info
or acc_info. 

Needed by which code?

> :- type	acc_info
> 	--->	simple(
> 			list(acc_var),
> 			sym_name,
> 			pred_id,
> 			proc_id
> 		).

Oh, I see you already used the name `acc_info'.
Documentation here, please.

> :- type rename
> 	--->	rename(
> 			list(var),
> 			list(var),
> 			module_info,
> 			set(var),		% Static
> 			set(var),		% Dynamic
> 			multi_map(var, var),	% Orig Var map
> 			map(var, rec_call)	% Prev call map
> 		).

Documentation here too, please.  (Static _what_?)

> :- type rec_call
> 	--->	assoc
> 	;	right_assoc.

... and here.

> :- type var_info
> 	--->	var_info(
> 			var,			% Headvar
> 			int			% location of Headvar
> 		).

... and here.  What's the purpose of this type -- what does a value
of type `var_info' represent?  And what's the location -- is that a
register number?

> :- type acc_var
> 	--->	acc_var(
> 			var_info,		% HeadVar (Y)
> 			var,			% Acc associated with Headvar
> 			var,			% Acc1 associated with Headvar
> 			var			% Y0
> 		).
> 
> :- type rec_goal
> 	--->	rec_goal(
> 			hlds_goals,		% Decompose
> 			hlds_goal,		% Call
> 			hlds_goals		% Compose
> 		).
> 
> :- type subgoal_type
> 	--->	recursive
> 	;	base.

More and/or better documentation is needed here too.

> 	%
> 	% Section of code that traverse all the predicates in a module
> 	% looking for opportunities to introduce accumulator recursion.
> 	%
> accumulator__introduction(ModuleInfo0, ModuleInfo) :-
> 	module_info_predids(ModuleInfo0, PredIds),
> 	accumulator__process_preds(PredIds, ModuleInfo0, ModuleInfo).
> 
> :- pred accumulator__process_preds(list(pred_id), module_info, module_info).
> :- mode accumulator__process_preds(in, in, out) is det.
> 
> accumulator__process_preds([], ModuleInfo, ModuleInfo).
> accumulator__process_preds([PredId | PredIds], ModuleInfo0, ModuleInfo) :-
> 	accumulator__process_pred(PredId, ModuleInfo0, ModuleInfo1),
> 	accumulator__process_preds(PredIds, ModuleInfo1, ModuleInfo).
> 
> 
> :- pred accumulator__process_pred(pred_id, module_info, module_info).
> :- mode accumulator__process_pred(in, in, out) is det.
> 
> accumulator__process_pred(PredId, ModuleInfo0, ModuleInfo) :-
> 	module_info_pred_info(ModuleInfo0, PredId, PredInfo),
> 	% pred_info_module(PredInfo, PredModule),
> 	% pred_info_name(PredInfo, PredName),
> 	% pred_info_arity(PredInfo, PredArity),
> 	pred_info_procids(PredInfo, ProcIds),
> 	accumulator__process_procs(PredId, ProcIds, ModuleInfo0, ModuleInfo).
> 
> :- pred accumulator__process_procs(pred_id, list(proc_id),
> 					module_info, module_info).
> :- mode accumulator__process_procs(in, in, in, out) is det.
> 
> accumulator__process_procs(_PredId, [], ModuleInfo, ModuleInfo).
> accumulator__process_procs(PredId, [ProcId | ProcIds], ModuleInfo0,
> 		ModuleInfo) :-
> 	module_info_preds(ModuleInfo0, PredTable0),
> 	map__lookup(PredTable0, PredId, PredInfo0),
> 	pred_info_procedures(PredInfo0, ProcTable0),
> 	map__lookup(ProcTable0, ProcId, ProcInfo0),
> 
> 	accumulator__process_proc(ProcId, ProcInfo0, PredId, PredInfo0,
> 					ModuleInfo0, ProcInfo,
> 					PredInfo1, ModuleInfo1),
> 
> 	pred_info_procedures(PredInfo1, ProcTable1),
> 	map__det_update(ProcTable1, ProcId, ProcInfo, ProcTable),
> 	pred_info_set_procedures(PredInfo1, ProcTable, PredInfo),
> 	module_info_preds(ModuleInfo1, PredTable1),
> 	map__det_update(PredTable1, PredId, PredInfo, PredTable),
> 	module_info_set_preds(ModuleInfo1, PredTable, ModuleInfo2),
> 
> 	accumulator__process_procs(PredId, ProcIds, ModuleInfo2, ModuleInfo).

You should use the routines in passes_aux.m instead of writing this
stuff manually.

> 	%
> 	%
> 	% accumulator__attempt_transform/8 is only true if the current
> 	% proc has been transformed into an accumulator recursion
> 	% version of the proc.
> 	%
> 	%
> :- pred accumulator__attempt_transform(proc_id, proc_info, pred_id, pred_info,
> 					module_info, proc_info,
> 					pred_info, module_info).
> :- mode accumulator__attempt_transform(in, in, in, in, in,
> 					out, out, out) is semidet.
> 
> 

As a style issue, I think the use of 

	%
	%
	% ....
	% ....
	%
	%

instead of

	%
	% ....
	% ....
	%

is probably not a good precedent.  I think the comment stands out well
enough with the latter style.

Similarly, one blank line between the type declaration and the clauses
is enough, IMHO -- you don't need two.

For consistency it would be better to use the same style as elsewhere
in the Mercury compiler.

> accumulator__attempt_transform(ProcId, ProcInfo0, PredId, PredInfo0,
> 				ModuleInfo0, ProcInfo, PredInfo, ModuleInfo) :-

This procedure is 100 lines long, which makes it difficult to read.
Could you break it up into smaller subroutines?

> accumulator__classify_vars_2([Mode|Modes], HeadVars, RecCallVars, 
...
> 			(
> 					%
> 					% This test codes up the case 
> 					% Y = Y0, which means that we
> 					% this variable is not a
> 					% recursive out variable.

"... that we this variable ..." doesn't parse.

What do you mean by "Y" and "Y0"?  Where did those variables come from?

> 	%
> 	% Ensure that an output variable is only allowed to depend on an
> 	% input variable by a direct assignment, and that all the goals
> 	% are atomic.
> 	%
> :- pred accumulator__check_orig_atomic_goal(hlds_goal_expr, set(var), set(var),
> 		set(var), set(var), bool).
> :- mode accumulator__check_orig_atomic_goal(in, in, in, out, out, 
> 		out) is semidet.
> 
> accumulator__check_orig_atomic_goal(Goal, StaticVars0, DynamicVars0, 
> 		StaticVars, DynamicVars, DeleteGoal) :-
> 	(
> 		(
> 			Goal = call(_, _, Vars, _, _, _)
> 		;
> 			Goal = higher_order_call(_, Vars, _, _, _, _)
> 		;
> 			Goal = pragma_c_code(_, _, _,Vars, _, _, _)
> 		;
> 			Goal = class_method_call(_, _, Vars, _, _, _)
> 		)
> 	->
> 		set__list_to_set(Vars, VarsSet),
> 		set__intersect(DynamicVars0, VarsSet, Intersect),
> 		set__empty(Intersect),
> 		set__union(StaticVars0, VarsSet, StaticVars),
> 		DynamicVars = DynamicVars0,
> 		DeleteGoal = no
> 	;
> 		Goal = unify(_, _, _, Unify, _),
> 		(
> 			Unify = assign(L, R),
> 			(
> 				set__member(R, DynamicVars0)
> 			->
> 				set__insert(DynamicVars0, L, DynamicVars),
> 				DeleteGoal = yes,
> 				StaticVars = StaticVars0
> 			;
> 				set__insert(StaticVars0, L, StaticVars),
> 				DeleteGoal = no,
> 				DynamicVars = DynamicVars0
> 			)
> 		;
> 			Unify = construct(_, _, Vars0, _),
> 			set__list_to_set(Vars0, VarsSet),
> 			set__intersect(DynamicVars0, VarsSet, Intersect),
> 			set__empty(Intersect),
> 			set__union(StaticVars0, VarsSet, StaticVars),
> 			DeleteGoal = no,
> 			DynamicVars = DynamicVars0
> 
> 		;
> 			Unify = deconstruct(_, _, Vars0, _, _),
> 			set__list_to_set(Vars0, VarsSet),
> 			set__intersect(DynamicVars0, VarsSet, Intersect),
> 			set__empty(Intersect),
> 			set__union(StaticVars0, VarsSet, StaticVars),
> 			DynamicVars = DynamicVars0,
> 			DeleteGoal = no
> 		;
> 			Unify = simple_test(_, _),
> 			StaticVars = StaticVars0,
> 			DynamicVars = DynamicVars0,
> 			DeleteGoal = no
> 		;
> 			Unify = complicated_unify(_, _),
> 			fail
> 		)
> 	).

Lots of duplicate code here.
Couldn't you use something like

	( Goal = unify(... assign(...) ...) ->
		... code to handle assignments ...
	; goal_is_atomic(Goal) ->
		goal_util__goal_vars(Goal, Vars),
		... code to handle other atomic goals ...
	;
		fail
	).

?

> 	%
> 	% accumulator__fix_classification/3 fixes up the set of
> 	% non recursive output vars.
> 	%
> :- pred accumulator__fix_classification(vars, list(var_info), list(var_info)).
> :- mode accumulator__fix_classification(in, in, out) is semidet.

How exactly does it fix them up?  What needs fixing?

> accumulator__fix_classification([], NonRecOutVars, NonRecOutVars).
> accumulator__fix_classification([Var | Vars], NonRecOutVars0, NonRecOutVars) :-
> 	accumulator__delete_var(Var, NonRecOutVars0, NonRecOutVars1),
> 	accumulator__fix_classification(Vars, NonRecOutVars1, NonRecOutVars).  

Hmm, perhaps it would be better to just rename this pred as
accumulator__delete_var_list.

> accumulator__swap_modes([var_info(_Var, P)|Vars], Modes0, Modes) :-

s/|/ | /

> 	accumulator__swap_modes(Vars, Modes0, Modes1),
> 	in_mode(InMode),
> 	(
> 		list__replace_nth(Modes1, P, InMode, Modes2)
> 	->
> 		Modes = Modes2
> 	;
> 		error("accumulator__swap_modes: never happen")
> 	).
> 
> 
> %-----------------------------------------------------------------------------%
> 
> 
> 	%
> 	% accumulator__process_cases/5
> 	%
> 	% Transform each of the cases to use accumulator recursion.
> 	%
> :- pred accumulator__process_cases(list(case), info, acc_info, list(var), 
> 		hlds_goals, module_info, list(case), hlds_goals).
> :- mode accumulator__process_cases(in, in, in, in, in, in, out, out) is semidet.

s/5/8/ or (better) just leave off the arity.

> :- pred accumulator__is_rec_goal(hlds_goal, pred_id, proc_id, rec_goal).
> :- mode accumulator__is_rec_goal(in, in, in, out) is semidet.
> 
> accumulator__is_rec_goal(conj(SubGoals) - _, PredId, ProcId, RecGoal) :-
> 	solutions(accumulator__rec_goal(SubGoals, PredId, ProcId), Solns),
> 	Solns = [RecGoal].

Documentation needed here -- I don't understand why you are using
nondeterminism and calling solutions/2.

> :- pred accumulator__rec_goal(hlds_goals, pred_id, proc_id, rec_goal).
> :- mode accumulator__rec_goal(in, in, in, out) is nondet.
> 
> accumulator__rec_goal(Goals, PredId, ProcId, RecGoal) :-
> 	append3(Decompose, SubGoal, Compose, Goals),
> 	SubGoal = call(PredId, ProcId, _, _, _, _) - _,
> 	\+ Compose = [],

I suggest `Compose \= []'.

> 	RecGoal = rec_goal(Decompose, SubGoal, Compose).
> 
> 
> :- pred append3(list(T), T, list(T), list(T)).
> :- mode append3(in, in, in, out) is det.
> :- mode append3(out, out, out, in) is nondet.
> 
> append3([], X, Xs, [X|Xs]).
> append3([X|Xs], Y, Ys, [X|Zs]) :-
> 	append3(Xs,Y,Ys,Zs).

append3 is normally used as the name of a predicate that appends three
lists together.

For the one you have above, it is simpler to just do

 	append(Decompose, [SubGoal | Compose], Goals),

> :- pred accumulator__rename_vars_in_goal(hlds_goal, rename, map(var, var),
> 		rename, hlds_goal).
> :- mode accumulator__rename_vars_in_goal(in, in, in, out, out) is semidet.
> 
> accumulator__rename_vars_in_goal(Goal0-GoalInfo0, Rename0, Subn, Rename,
> 		Goal-GoalInfo) :-

s/-/ - /g

This predicate should be documented.  How is it different from
the ones in goal_util.m?  In fact, why is it here, rather than in goal_util.m?

> 		%
> 		% We can only have a if-then-else if we only
> 		% update static variables.
> 		%

This comment is quite mysterious to me, because I don't know what you
mean by static variables.

> accumulator__name_apart_2(
> 		call(PredId, ProcId, Args0, Builtin, Context, Sym),
> 		Rename0, Subn, Rename,
> 		call(PredId, ProcId, Args, Builtin, Context, Sym)) :-

This is another 98-line clause.  It would be much easier to read
if you could break it up into subroutines.

> :- pred accumulator__unknown_assoc_call(list(var), rename, rename).
> :- mode accumulator__unknown_assoc_call(in, in, out) is semidet.
> 
> accumulator__unknown_assoc_call(Vars0, Rename0, Rename) :-
> 	Rename0 = rename(Ys, Y0s, ModuleInfo, DynamicSet, StaticSet0, 
> 			OrigDynMap, PrevCallMap),
> 	(
> 			%
> 			% We don't know the assocativity of the current

s/assocativity/associativity/

> 	%
> 	% 
> 	%
> :- pred accumulator__search_prevcalls(list(var), map(var, rec_call), 
> 		maybe(rec_call), rec_call).
> :- mode accumulator__search_prevcalls(in, in, in, out) is semidet.

Obviously you too thought you should document this one ;-)

> 	%
> 	% If accumulator_is_assocative is true is returns a reodering

s/reoder/reorder/

> :- pred assoc_fact(module_name, string, arity, list(mode), module_info, 
> 		list(var), list(var), bool).
> :- mode assoc_fact(in, in, in, in, in, in, out, out) is semidet.
> 
> assoc_fact(unqualified("int"), "+", 3, [In, In, Out], ModuleInfo, 
> 		[A, B, C], [A, B, C], no) :-
> 	mode_is_input(ModuleInfo, In),
> 	mode_is_output(ModuleInfo, Out).
> 
> assoc_fact(unqualified("float"), "+", 3, [In, In, Out], ModuleInfo, 
> 		[A, B, C], [A, B, C], no) :-
> 	mode_is_input(ModuleInfo, In),
> 	mode_is_output(ModuleInfo, Out).
> 
> assoc_fact(unqualified("int"), "*", 3, [In, In, Out], ModuleInfo, 
> 		[A, B, C], [A, B, C], no) :-
> 	mode_is_input(ModuleInfo, In),
> 	mode_is_output(ModuleInfo, Out).
> 
> assoc_fact(unqualified("float"), "*", 3, [In, In, Out], ModuleInfo, 
> 		[A, B, C], [A, B, C], no) :-
> 	mode_is_input(ModuleInfo, In),
> 	mode_is_output(ModuleInfo, Out).

Floating point multiplication and addition are not actually associative.
Neither are fixed-precision integer multiplication, if you actually
check for overflow; currently we don't, but maybe we will in the future.

If you want the compiler to treat them as associative, there should
be a compiler option to control this, and it should probably be off
by default.


So, I would like you to put a lot more effort into the documentation,
address the other points raised above, and then send another diff. 
I'm sure I will have some more comments once I understand it a bit
better, so I expect that won't be the last diff either.

Cheers,
	Fergus.

-- 
Fergus Henderson <fjh at cs.mu.oz.au>  |  "I have always known that the pursuit
WWW: <http://www.cs.mu.oz.au/~fjh>  |  of excellence is a lethal habit"
PGP: finger fjh at 128.250.37.3        |     -- the last words of T. S. Garp.



More information about the developers mailing list