[m-dev.] for review: constraint propagation

Fergus Henderson fjh at cs.mu.OZ.AU
Fri Feb 25 21:52:02 AEDT 2000


On 23-Feb-2000, Simon Taylor <stayl at cs.mu.OZ.AU> wrote:
> 
> Constraint propagation.

Great!

A few general comments:

      -	Constraint propagation might not preserve unique-mode-correctness.
	Do you check to ensure that unique-mode-correctness is preserved?

      - Constraint propagation might also not preserve determinism-correctness.
       	You need to be careful not to move constraints before calls to
	cc_nondet or cc_multi procedures.  Do you do that?

      -	Constraint propagation should be disabled if `--no-reorder-conj'
	is set.

> compiler/options.m:
> 	Add documentation for `--constraint-propagation'.
> 
> 	Add option `--local-constraint-propagation', which makes
> 	deforestation call constraint.m to move constraints within
> 	a goal, but does not create specialized versions of procedures
> 	for which there are calls with constrained outputs.

Does the compiler bootstrap and pass its tests
with constraint propagation enabled?
If not, then it would probably be a good idea to
find out why not ;-)
If so, then you should enable constraint propagation
at one of the `-O' levels, e.g. -O3 or -O4.

Also, it would be nice to know if constraint propagation
has any effects on the compiler's size and speed
(I suspect it should have little effect;
other kinds of applications would be more likely
to benefit).

> +++ NEWS	2000/02/18 02:01:42
> @@ -24,6 +24,16 @@
>  * We've generalized the higher-order term syntax a little:
>    in `Foo(Args)', we now allow Foo to be any term, not just
>    a variable.
> +
> +Changes to the Mercury implementation:
> +
> +* We've added a new transformation -- constraint propagation.
> +
> +  Constraint propagation attempts to transform the code so
> +  that goals which can fail are executed as early as possible.
> +  It is enabled with the `--constraint-propagation' option
> +  (or `--local-constraint-propagation' for a more restricted
> +  version of the transformation).

If you enable constraint propagation at one of the `-O' levels,
that should be mentioned here.

constraint.m:
> :- pred constraint__propagate_goal(hlds_goal, list(constraint),
> 		hlds_goal, constraint_info, constraint_info).
> :- mode constraint__propagate_goal(in, in, out, 
> 		in, out) is det.
> 
> :- pred constraint__propagate_conj(list(hlds_goal), list(constraint), 
> 		list(hlds_goal), constraint_info, constraint_info).
> :- mode constraint__propagate_conj(in, in, out,
> 		in, out) is det.

These predicates should be documented.  It's not immediately clear what the
relationship between the different arguments is.

> :- pred constraint_info_init(module_info, map(prog_var, type), prog_varset,
> 		instmap, constraint_info).
> :- mode constraint_info_init(in, in, in, in, out) is det.
> 
> :- pred constraint_info_deconstruct(constraint_info, module_info,
> 		map(prog_var, type), prog_varset, bool).
> :- mode constraint_info_deconstruct(in, out, out, out, out) is det.
>
> :- type constraint_info.

I suggest you declare the type before declaring the
predicates that operate on it.  I find that this usually
makes it a bit easier to read.

> 	% A constraint is a goal with no outputs which can fail and
> 	% always terminates, and a list of goals to construct static
> 	% constants for the constraint.  All the goals should have a
> 	% `constraint' annotation.
> :- type constraint == pair(hlds_goal, list(hlds_goal)).

The documentation of the list of goals is not entirely clear to me.
Is there any invariant relating the goal to the list of goals?

> constraint__propagate_goal(Goal0, Constraints, Goal) -->
> 	{ Goal0 = _ - GoalInfo0 },
> 	
> 	% 
> 	% If the goal cannot succeed, prune away the constraints.
> 	% This is necessary because the goal might not produce some
> 	% of the inputs to the constraints, so reordering the constraints
> 	% with the goal may cause compiler aborts later.

I suggest replacing "may cause compiler aborts later" with
"might violate mode correctness, which could cause compiler aborts later".

> constraint__propagate_goal_2(
> 		if_then_else(Vars, Cond0, Then0, Else0, SM) - Info,
> 		Constraints, 
> 		[if_then_else(Vars, Cond, Then, Else, SM) - Info]) -->
> 	InstMap0 =^ instmap,
> 	constraint_info_update_changed(Constraints),
> 
> 	% We can't safely propagate constraints into 
> 	% the condition of an if-then-else.

I think it might be worth explaining here in the comment
why that isn't safe.

> 	% XXX propagate constraints into par_conjs - could be a little tricky.
> constraint__propagate_goal_2(par_conj(Goals0, SM) - GoalInfo, Constraints0,
> 		[par_conj(Goals, SM) - GoalInfo | Constraints]) -->
> 	% constraint__propagate_disj treats its list of goals as
> 	% independent rather than specifically disjoint, so we can
> 	% use it to process a list of independent parallel conjuncts.
> 	constraint__propagate_disj(Goals0, [], Goals),
> 	{ constraint__flatten_constraints(Constraints0, Constraints) }.

Currently we require par_conjs to be model_det.
So propagating constraints into them would violate
determinism-correctness.

So for now, I suggest that you not try to propagate constraints
into par_conjs.

> constraint__propagate_goal_2(Goal, Constraints0, [Goal | Constraints]) -->
> 	{ Goal = call(_, _, _, _, _, _) - _ },
> 	{ constraint__flatten_constraints(Constraints0, Constraints) }.

Hmm, so you don't propagate constraints past calls?

If I write

	:- mode p(in, out) is semidet.
	p(X, Y) :-
		q(X, Y),
		test(X).

	:- mode q(in, out) is det.

shouldn't the constraint propagation optimize that to

	p(X, Y) :-
		test(X),
		q(X, Y).

?

But from the code above, it looks like it won't do that.

Maybe I misunderstood your code.  If so, perhaps a comment
here would help.

> :- pred constraint__propagate_disj(list(hlds_goal), list(constraint),
> 		list(hlds_goal), constraint_info, constraint_info).
> :- mode constraint__propagate_disj(in, in, out, 
> 		in, out) is det.
> 
> constraint__propagate_disj([], _, []) --> [].
> constraint__propagate_disj([Goal0 | Goals0], Constraints, [Goal | Goals]) -->
> 	InstMap0 =^ instmap,
> 	constraint__propagate_goal(Goal0, Constraints, Goal),
> 	^ instmap := InstMap0,
> 	constraint__propagate_disj(Goals0, Constraints, Goals).

Here you propagate the constraints into all the disjuncts in a disjunction.
That might increase code size, so it bears thinking about.
What's the worst-case scenario?
Would there be cases where enabling constraint propagation
will end up increasing code size with no benefit?
If so, is there anything we can do to avoid such cases?

> constraint__annotate_conj_output_vars([Goal | Goals], ModuleInfo, InstMap0, 
> 		RevGoals0, RevGoals) :-
> 	Goal = _ - GoalInfo,
> 	goal_info_get_instmap_delta(GoalInfo, InstMapDelta),
> 
> 	% XXX this won't work on the alias branch.
> 	instmap_delta_changed_vars(InstMapDelta, ChangedVars0),
> 	Bound = lambda([Var::in] is semidet, (
> 			instmap__lookup_var(InstMap0, Var, InstMapInst),
> 			instmap_delta_search_var(InstMapDelta, Var, DeltaInst),
> 			\+ inst_matches_binding(InstMapInst,
> 				DeltaInst, ModuleInfo)
> 		)),
> 	set__to_sorted_list(ChangedVars0, ChangedVars1),
> 	list__filter(Bound, ChangedVars1, ChangedVars2),
> 	set__sorted_list_to_set(ChangedVars2, ChangedVars),

It would be nice to add `set__filter'.
That could be a separate change, though.

> constraint__annotate_conj_constraints(ModuleInfo, 
> 		[Goal - OutputVars | RevGoals0], 
> 		Constraints0, Goals0, Goals) -->
> 	{ Goal = GoalExpr - GoalInfo },
> 	(
> 		% Propagate goals with no output variables which can fail.
> 		{ goal_info_get_determinism(GoalInfo, Detism) },
> 		{ Detism = semidet
> 		; Detism = failure
> 		% ; Detism = cc_nondet	% ??

It's possible to propagate cc_nondet constraints.
But you need to ensure that you do not move them
before any goal that might fail.  That might require
some care if there are a mixture of constraints,
some of which are semidet and one of which is cc_nondet;
you need to be careful that you don't end up changing
the relative ordering of the different constraints.

> :- pred constraint__add_constant_construction(prog_var::in, hlds_goal::in,
> 		list(constraint)::in, list(constraint)::out,
> 		constraint_info::in, constraint_info::out) is det.
> 
> constraint__add_constant_construction(_, _, [], []) --> [].
> constraint__add_constant_construction(ConstructVar, Construct0,
> 		[Constraint0 - Constructs0 | Constraints0],
> 		[Constraint - Constructs | Constraints]) -->
> 	(
> 		{
> 		Constraint0 = _ - ConstraintInfo,
> 		goal_info_get_nonlocals(ConstraintInfo, ConstraintNonLocals),
> 		set__member(ConstructVar, ConstraintNonLocals)
> 		}
> 	->

For consistency with the layout used in the rest of the compiler,
I suggest you use

	(
		{ ... },
		{ ... },
		{ ... }
	->

rather than

	(
		{
		...
		...
		...
		}
	->

inlining.m:
> +	% inlining__can_inline_proc(PredInfo, ProcId, BuiltinState,
> +	%	CallingPredMarkers).
> +	%
> +	% Succeed if the called predicate can be inlined into the caller.
> +	% Possible reasons for this failing are
> +	% - the called predicate is imported
> +	% - the called predicate is a builtin
> +	% - the called predicate is tabled
> +	% - the called predicate has a no_inline marker
> +	% - the called predicate is an Aditi procedure and the caller
> +	% 	is not (inlining such procedures can cause severe
> +	% 	slowdowns by performing joins using backtracking rather
> +	% 	than using specialized algorithms in the database.

That comment is missing a ')'.

> Index: compiler/mercury_compile.m
> ===================================================================
> RCS file: /home/mercury1/repository/mercury/compiler/mercury_compile.m,v
> retrieving revision 1.148
> diff -u -u -r1.148 mercury_compile.m
> --- compiler/mercury_compile.m	2000/02/10 04:37:38	1.148
> +++ compiler/mercury_compile.m	2000/02/10 04:48:35
> @@ -1731,7 +1731,9 @@
>  
>  mercury_compile__maybe_deforestation(HLDS0, Verbose, Stats, HLDS) -->
>  	globals__io_lookup_bool_option(deforestation, Deforest),
> -	( { Deforest = yes } ->
> +	globals__io_lookup_bool_option(local_constraint_propagation,
> +		Constraints),
> +	( { Deforest = yes ; Constraints = yes } ->
>  		maybe_write_string(Verbose, "% Deforestation...\n"),

If deforestation is not enabled, it seems misleading
to print out "Deforestation...".

I think it might be beter if you change the message so that it prints
out either "Deforestation", "Deforestation and constraint propagation",
or "Constraint propagation", depending on which combination of options
is selected.  Does that sound reasonable?

> @@ -2074,8 +2078,14 @@
>  		"\tdetects only common deconstruction unifications.",
>  		"\tDisabling this optimization reduces the class of predicates",
>  		"\tthat the compiler considers to be deterministic.",
> -	% 	"\t--constraint-propagation",
> -	% 	"\t\tEnable the C-tranformation.  (Doesn't work.)",
> +	 	"--constraint-propagation",
> +	 	"\tEnable the constraint propagation transformation,",
> +		"\twhich attempts to execute goals which can fail as",
> +		"\tearly as possible.",
> +	 	"--local-constraint-propagation",
> +	 	"\tEnable the constraint propagation transformation,",
> +		"\tbut don't create specialized versions of predicates",
> +		"\twhen performing the transformation.",

s/predicate/procedure/

I think it would be better if you could make it clear that
"local" means "within a procedure".

> Index: compiler/pd_util.m
> ===================================================================
> RCS file: /home/mercury1/repository/mercury/compiler/pd_util.m,v
> retrieving revision 1.7
> diff -u -u -r1.7 pd_util.m
> --- compiler/pd_util.m	1999/10/15 03:45:01	1.7
> +++ compiler/pd_util.m	2000/02/08 05:57:56
> @@ -21,6 +21,10 @@
>  :- pred pd_util__goal_get_calls(hlds_goal::in,
>  		list(pred_proc_id)::out) is det.
>  
> +:- pred pd_util__propagate_constraints(hlds_goal::in, list(hlds_goal)::in,
> +		set(prog_var)::in, hlds_goal::out,
> +		pd_info::pd_info_di, pd_info::pd_info_uo) is det.

That predicate should be documented.
(So should the other predicates exported by this module.)

> +++ w3/news/newsdb.inc	2000/02/23 05:02:53
> @@ -21,6 +21,14 @@
>  
>  $newsdb = array(
>  
> +"24 Feb 2000" => array("Constraint propagation",

Don't forget to change that date to whatever is appropriate
when you actually commit this change.

> --- doc/user_guide.texi	2000/01/10 00:43:58	1.200
...
> + at item --constraint-propagation
> +Enable the constraint propagation transformation, which attempts
> +to execute goals which can fail as early as possible.
> +
> + at item --local-constraint-propagation
> +Enable the constraint propagation transformation, but do not
> +create specialized versions of predicates when performing the
> +transformation.

See my comments on options.m.


Apart from those points, this change looks good.

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