[m-rev.] for review: fix lost `impure' goal features

Simon Taylor stayl at cs.mu.OZ.AU
Fri Feb 28 11:20:48 AEDT 2003


On 28-Feb-2003, Fergus Henderson <fjh at cs.mu.OZ.AU> wrote:
> On 28-Feb-2003, Simon Taylor <stayl at cs.mu.OZ.AU> wrote:
> > 
> > Fix bugs in the handling of purity in the optimization passes
> > (in particular constraint propagation), which caused purity
> > annotations on goals to be lost. This caused
> > tests/tabling/unused_args to fail on earth.

> Calls to goal_info_init/4 are probably quite frequent, so I think it is
> worth manually inlining the calls to goal_info_init/1 and goal_info_set_*,
> and computing the goal_features directly from the purity (this could
> still be done by a predicate in purity.m, but one that just returns
> a set of goal_features rather than a goal_info).

Estimated hours taken: 8
Branches: main, release

Fix bugs in the handling of purity in the optimization passes
(in particular constraint propagation), which caused purity
annotations on goals to be lost. This caused
tests/tabling/unused_args to fail on earth.

compiler/hlds_goal.m:
	Make the version of goal_info_init called from
	the optimization passes take the purity as an
	argument. Previously, callers were constructing
	a goal_info then adding the purity, which was
	error prone.

compiler/hlds_goal.m:
compiler/purity.m:
	Move the predicates to deal with purity representation
	in hlds_goal_infos into hlds_goal.m. Rationale -
	goal_info_get_determinism is not in det_analysis.m,
	goal_info_get_nonlocals is not in quantification.m, etc.
	This makes it easier to make the purity setting code
	efficient.

	Don't allocate memory in add_goal_info_purity_feature
	if the call doesn't change the purity.

compiler/*.m:
	Pass the extra argument to goal_info_init.

compiler/polymorphism.m:
	Remove a duplicate definition of
	hlds_goal__make_int_const_construction.

compiler/magic.m:
	Remove some unused code.

tests/hard_coded/purity/Mmakefile:
tests/hard_coded/purity/Mercury.options:
tests/hard_coded/purity/purity_opt.{m,exp}:
	Test case.

diff -u compiler/hlds_goal.m compiler/hlds_goal.m
--- compiler/hlds_goal.m
+++ compiler/hlds_goal.m
@@ -706,6 +706,23 @@
 :- pred goal_has_feature(hlds_goal, goal_feature).
 :- mode goal_has_feature(in, in) is semidet.
 
+%  Update a goal info to reflect the specified purity
+:- pred add_goal_info_purity_feature(hlds_goal_info, purity, hlds_goal_info).
+:- mode add_goal_info_purity_feature(in, in, out) is det.
+
+%  Determine the purity of a goal from its hlds_goal_info.
+:- pred infer_goal_info_purity(hlds_goal_info, purity).
+:- mode infer_goal_info_purity(in, out) is det.
+
+%  Check if a hlds_goal_info is for a pure goal
+:- pred goal_info_is_pure(hlds_goal_info).
+:- mode goal_info_is_pure(in) is semidet.
+
+%  Check if a hlds_goal_info is for an impure goal.  Fails if the goal is
+%  semipure, so this isn't the same as \+ goal_info_is_pure.
+:- pred goal_info_is_impure(hlds_goal_info).
+:- mode goal_info_is_impure(in) is semidet.
+
 :- type goal_feature
 	--->	constraint	% This is included if the goal is
 				% a constraint.  See constraint.m
@@ -889,6 +906,10 @@
 :- pred goal_list_determinism(list(hlds_goal), determinism).
 :- mode goal_list_determinism(in, out) is det.
 
+	% Compute the purity of a list of goals. 
+:- pred goal_list_purity(list(hlds_goal), purity).
+:- mode goal_list_purity(in, out) is det.
+
 	% Change the contexts of the goal_infos of all the sub-goals
 	% of the given goal. This is used to ensure that error messages
 	% for automatically generated unification procedures have a useful
@@ -1216,6 +1237,7 @@
 		code_gen_info :: hlds_goal_code_gen_info
 	).
 
+:- pragma inline(goal_info_init/1).
 goal_info_init(GoalInfo) :-
 	Detism = erroneous,
 	instmap_delta_init_unreachable(InstMapDelta),
@@ -1225,24 +1247,25 @@
 	GoalInfo = goal_info(Detism, InstMapDelta, Context, NonLocals,
 		Features, [], no_code_gen_info).
 
+:- pragma inline(goal_info_init/2).
 goal_info_init(Context, GoalInfo) :-
-	goal_info_init(GoalInfo0),
-	goal_info_set_context(GoalInfo0, Context, GoalInfo).
+	Detism = erroneous,
+	instmap_delta_init_unreachable(InstMapDelta),
+	set__init(NonLocals),
+	set__init(Features),
+	GoalInfo = goal_info(Detism, InstMapDelta, Context, NonLocals,
+		Features, [], no_code_gen_info).
 
 goal_info_init(NonLocals, InstMapDelta, Detism, Purity, GoalInfo) :-
-	goal_info_init(GoalInfo0),
-	goal_info_set_nonlocals(GoalInfo0, NonLocals, GoalInfo1),
-	goal_info_set_instmap_delta(GoalInfo1, InstMapDelta, GoalInfo2),
-	goal_info_set_determinism(GoalInfo2, Detism, GoalInfo3),
-	add_goal_info_purity_feature(GoalInfo3, Purity, GoalInfo).
+	term__context_init(Context),
+	purity_features(Purity, _, Features),
+	GoalInfo = goal_info(Detism, InstMapDelta, Context, NonLocals,
+		list_to_set(Features), [], no_code_gen_info).
 
 goal_info_init(NonLocals, InstMapDelta, Detism, Purity, Context, GoalInfo) :-
-	goal_info_init(GoalInfo0),
-	goal_info_set_nonlocals(GoalInfo0, NonLocals, GoalInfo1),
-	goal_info_set_instmap_delta(GoalInfo1, InstMapDelta, GoalInfo2),
-	goal_info_set_determinism(GoalInfo2, Detism, GoalInfo3),
-	goal_info_set_context(GoalInfo3, Context, GoalInfo4),
-	add_goal_info_purity_feature(GoalInfo4, Purity, GoalInfo).
+	purity_features(Purity, _, Features),
+	GoalInfo = goal_info(Detism, InstMapDelta, Context, NonLocals,
+		list_to_set(Features), [], no_code_gen_info).
 
 goal_info_get_determinism(GoalInfo, GoalInfo ^ determinism).
 
@@ -1289,6 +1312,44 @@
 
 %-----------------------------------------------------------------------------%
 
+add_goal_info_purity_feature(GoalInfo0, Purity, GoalInfo) :-
+	infer_goal_info_purity(GoalInfo0, Purity0),
+	( Purity = Purity0 ->
+		GoalInfo = GoalInfo0
+	;
+		purity_features(Purity, FeaturesToRemove, FeaturesToAdd),
+		goal_info_get_features(GoalInfo0, Features0),
+		Features = set__union(list_to_set(FeaturesToAdd),
+				set__difference(Features0,
+					list_to_set(FeaturesToRemove))),
+		goal_info_set_features(GoalInfo0, Features, GoalInfo)
+	).
+
+:- pred purity_features(purity::in, list(goal_feature)::out,
+		list(goal_feature)::out) is det.
+
+purity_features(pure, [(impure), (semipure)], []).
+purity_features((semipure), [(impure)], [(semipure)]).
+purity_features((impure), [(semipure)], [(impure)]).
+
+infer_goal_info_purity(GoalInfo, Purity) :-
+	( goal_info_has_feature(GoalInfo, (impure)) ->
+		Purity = (impure)
+	; goal_info_has_feature(GoalInfo, (semipure)) ->
+		Purity = (semipure)
+	;
+		Purity = pure
+	).
+			
+goal_info_is_pure(GoalInfo) :-
+	\+ goal_info_has_feature(GoalInfo, (impure)),
+	\+ goal_info_has_feature(GoalInfo, (semipure)).
+	
+goal_info_is_impure(GoalInfo) :-
+	goal_info_has_feature(GoalInfo, (impure)).
+	
+%-----------------------------------------------------------------------------%
+
 goal_info_add_feature(GoalInfo0, Feature, GoalInfo) :-
 	goal_info_get_features(GoalInfo0, Features0),
 	set__insert(Features0, Feature, Features),
@@ -1568,6 +1629,13 @@
 
                )),
        list__foldl(ComputeDeterminism, Goals, det, Determinism).
+
+goal_list_purity(Goals, Purity) :-
+	Purity = list__foldl(
+			(func(_ - GoalInfo, Purity0) = Purity1 :-
+				infer_goal_info_purity(GoalInfo, GoalPurity),
+		    		worst_purity(GoalPurity, Purity0, Purity1)
+			), Goals, pure).
 
 %-----------------------------------------------------------------------------%
 
only in patch2:
--- compiler/purity.m	22 Feb 2003 13:18:28 -0000	1.52
+++ compiler/purity.m	27 Feb 2003 15:45:37 -0000
@@ -118,9 +118,9 @@
 :- module check_hlds__purity.
 :- interface.
 
-:- import_module parse_tree__prog_data, hlds__hlds_module, hlds__hlds_goal.
+:- import_module parse_tree__prog_data, hlds__hlds_module.
 :- import_module hlds__hlds_pred.
-:- import_module io, bool, list.
+:- import_module io, bool.
 
 % The purity type itself is defined in prog_data.m as follows:
 % :- type purity	--->	pure
@@ -172,27 +172,6 @@
 :- mode purity_name(in, out) is det.
 :- mode purity_name(out, in) is semidet.
 
-%  Update a goal info to reflect the specified purity
-:- pred add_goal_info_purity_feature(hlds_goal_info, purity, hlds_goal_info).
-:- mode add_goal_info_purity_feature(in, in, out) is det.
-
-%  Determine the purity of a goal from its hlds_goal_info.
-:- pred infer_goal_info_purity(hlds_goal_info, purity).
-:- mode infer_goal_info_purity(in, out) is det.
-
-%  Check if a hlds_goal_info is for a pure goal
-:- pred goal_info_is_pure(hlds_goal_info).
-:- mode goal_info_is_pure(in) is semidet.
-
-%  Check if a hlds_goal_info is for an impure goal.  Fails if the goal is
-%  semipure, so this isn't the same as \+ goal_info_is_pure.
-:- pred goal_info_is_impure(hlds_goal_info).
-:- mode goal_info_is_impure(in) is semidet.
-
-% Work out the purity of a list of goals. 
-:- pred goal_list_purity(list(hlds_goal), purity).
-:- mode goal_list_purity(in, out) is det.
-
 % Give an error message for unifications marked impure/semipure that are  
 % not function calls (e.g. impure X = 4)
 :- pred impure_unification_expr_error(prog_context, purity,
@@ -201,7 +180,7 @@
 
 :- implementation.
 
-:- import_module hlds__hlds_data, parse_tree__prog_io_util.
+:- import_module hlds__hlds_data, hlds__hlds_goal, parse_tree__prog_io_util.
 :- import_module check_hlds__type_util, check_hlds__mode_util.
 :- import_module ll_backend__code_util, parse_tree__prog_data.
 :- import_module check_hlds__unify_proc.
@@ -213,7 +192,7 @@
 :- import_module check_hlds__post_typecheck.
 
 :- import_module map, varset, term, string, require, std_util.
-:- import_module assoc_list, bool, int, set.
+:- import_module assoc_list, bool, int, list, set.
 
 %-----------------------------------------------------------------------------%
 %				Public Predicates
@@ -243,49 +222,8 @@
 worst_purity((impure), (semipure), (impure)).
 worst_purity((impure), (impure), (impure)).
 
-
 less_pure(P1, P2) :-
 	\+ worst_purity(P1, P2, P2).
-
-
-add_goal_info_purity_feature(GoalInfo0, pure, GoalInfo) :-
-	goal_info_remove_feature(GoalInfo0, (semipure), GoalInfo1),
-	goal_info_remove_feature(GoalInfo1, (impure), GoalInfo).
-add_goal_info_purity_feature(GoalInfo0, (semipure), GoalInfo) :-
-	goal_info_remove_feature(GoalInfo0, (impure), GoalInfo1),
-	goal_info_add_feature(GoalInfo1, (semipure), GoalInfo).
-add_goal_info_purity_feature(GoalInfo0, (impure), GoalInfo) :-
-	goal_info_remove_feature(GoalInfo0, (semipure), GoalInfo1),
-	goal_info_add_feature(GoalInfo1, (impure), GoalInfo).
-
-
-infer_goal_info_purity(GoalInfo, Purity) :-
-	(
-	    goal_info_has_feature(GoalInfo, (impure)) ->
-		Purity = (impure)
-	;
-	    goal_info_has_feature(GoalInfo, (semipure)) ->
-		Purity = (semipure)
-	;
-		Purity = pure
-	).
-
-
-goal_list_purity(Goals, Purity) :-
-	Purity = list__foldl(
-			(func(_ - GoalInfo, Purity0) = Purity1 :-
-				infer_goal_info_purity(GoalInfo, GoalPurity),
-		    		worst_purity(GoalPurity, Purity0, Purity1)
-			), Goals, pure).
-			
-goal_info_is_pure(GoalInfo) :-
-	\+ goal_info_has_feature(GoalInfo, (impure)),
-	\+ goal_info_has_feature(GoalInfo, (semipure)).
-	
-
-goal_info_is_impure(GoalInfo) :-
-	goal_info_has_feature(GoalInfo, (impure)).
-	
 
 % this works under the assumptions that all purity names but `pure' are prefix
 % operators, and that we never need `pure' indicators/declarations.
only in patch2:
--- compiler/loop_inv.m	1 Nov 2002 01:59:17 -0000	1.2
+++ compiler/loop_inv.m	27 Feb 2003 16:04:01 -0000
@@ -416,7 +416,7 @@
 invariant_goal_candidates_handle_non_recursive_call(
         Goal @ (_GoalExpr - GoalInfo), IGCs) =
     ( if   not model_non(GoalInfo),
-           purity__goal_info_is_pure(GoalInfo)
+           goal_info_is_pure(GoalInfo)
       then IGCs ^ path_candidates := [Goal | IGCs ^ path_candidates]
       else IGCs
     ).
@@ -645,7 +645,7 @@
 :- mode impure_goal(in) is semidet.
 
 impure_goal(_GoalExpr - GoalInfo) :-
-    purity__goal_info_is_impure(GoalInfo).
+    goal_info_is_impure(GoalInfo).
 
 %------------------------------------------------------------------------------%
 
--------------------------------------------------------------------------
mercury-reviews mailing list
post:  mercury-reviews at cs.mu.oz.au
administrative address: owner-mercury-reviews at cs.mu.oz.au
unsubscribe: Address: mercury-reviews-request at cs.mu.oz.au Message: unsubscribe
subscribe:   Address: mercury-reviews-request at cs.mu.oz.au Message: subscribe
--------------------------------------------------------------------------



More information about the reviews mailing list