[m-dev.] for review: improvements to type specialization [2]

Simon Taylor stayl at cs.mu.OZ.AU
Fri Oct 1 14:25:51 AEST 1999


Thanks David, here's a relative diff addressing your comments.

Simon.

--- log	1999/10/01 02:23:29	1.1
+++ log	1999/10/01 04:15:30
@@ -7,10 +7,13 @@
 compiler/higher_order.m:
 	Only add extra type-infos, not typeclass-infos when
 	--typeinfo-liveness is set, extracting type-infos from
-	typeclass-infos where necessary. This avoids the need to
-	work out how to order any extra typeclass-infos, and
-	maximises the chance of multiple specialized calls to the same
-	procedure being able to use the same code.
+	typeclass-infos where necessary. The arguments of the
+	specialized version are now independent of the class context
+	of the requesting procedure, which maximises the chance of multiple
+	specialized calls to the same procedure being able to use the
+	same code. The code to specialize calls is now slightly simpler
+	because it does not have to work out how to order extra
+	typeclass-info arguments.
 
 	Specialize special preds for no-tag types where the
 	wrapped type is an atomic type and the no-tag type does not
@@ -61,8 +64,9 @@
 	Use the new predicates in varset.m to avoid adding the variable
 	names from the declarations of equivalence types into the tvarsets
 	of declarations which use those types. This is needed so that
-	`varset__create_name_var_map' is not confused by multiple occurrences
-	of a variable name.
+	`varset__create_name_var_map' (used by make_hlds.m for
+	`:- pragma type_spec' declarations and explicit type qualifications)
+	is not confused by multiple occurrences of a variable name.
 
 doc/reference_manual.texi:
 	Remove documentation of the limitation that the substituted types

--- equiv_type.m	1999/10/01 01:31:54	1.1
+++ equiv_type.m	1999/10/01 04:22:11
@@ -411,6 +411,18 @@
 		(	
 			map__search(EqvMap, EqvTypeId,
 				eqv_type_body(EqvVarSet, Args0, Body0)),
+			%
+			% Don't merge in the variable names from the
+			% type declaration to avoid creating multiple
+			% variables with the same name so that
+			% `varset__create_name_var_map' can be used
+			% on the resulting tvarset.
+			% make_hlds.m uses `varset__create_name_var_map' to
+			% match up type variables in `:- pragma type_spec'
+			% declarations and explicit type qualifications
+			% with the type variables in the predicate's
+			% declaration.
+			%
 			varset__merge_without_names(VarSet1, EqvVarSet,
 				[Body0 | Args0], VarSet2, [Body | Args]),
 			Circ0 = no,
--- higher_order.m	1999/10/01 01:31:54	1.1
+++ higher_order.m	1999/10/01 04:02:08
@@ -309,7 +309,7 @@
 		PredProcId = proc(PredId, ProcId),
 		Info0 = info(PredVars0, Requests0, NewPreds, PredProcId,
 			PredInfo0, ProcInfo0, ModuleInfo0, Params, unchanged),
-		traverse_goal_0(Info0, Info),
+		traverse_goal(Info0, Info),
 		Info = info(_, Requests1, _, _, PredInfo1, ProcInfo,
 				ModuleInfo1, _, _),
 		proc_info_goal(ProcInfo, Goal1),
@@ -345,7 +345,7 @@
 	map__lookup(Procs0, ProcId, ProcInfo0),
 	Info0 = info(PredVars0, Requests0, NewPreds, proc(PredId, ProcId),
 			PredInfo0, ProcInfo0, ModuleInfo0, Params, unchanged),
-	traverse_goal_0(Info0, Info),
+	traverse_goal(Info0, Info),
 	Info = info(_, Requests1, _,_,PredInfo1,ProcInfo,ModuleInfo1,_,_),
 	map__det_update(Procs0, ProcId, ProcInfo, Procs1),
 	traverse_other_procs(Params, PredId, ProcIds, ModuleInfo1, ModuleInfo,
@@ -355,16 +355,16 @@
 %-------------------------------------------------------------------------------
 	% Goal traversal
 
-:- pred traverse_goal_0(higher_order_info::in, higher_order_info::out) is det.
+:- pred traverse_goal(higher_order_info::in, higher_order_info::out) is det.
 
-traverse_goal_0 -->
+traverse_goal -->
 	{ MustRecompute = no },
-	traverse_goal_0(MustRecompute).
+	traverse_goal(MustRecompute).
 
-:- pred traverse_goal_0(bool::in, higher_order_info::in,
+:- pred traverse_goal(bool::in, higher_order_info::in,
 		higher_order_info::out) is det.
 
-traverse_goal_0(MustRecompute, Info0, Info) :-
+traverse_goal(MustRecompute, Info0, Info) :-
 	Info0 = info(_, B, NewPreds0, PredProcId, E, ProcInfo0, G, H, I),
 	NewPreds0 = new_preds(_, PredVarMap),
 
@@ -377,7 +377,7 @@
 		Info1 = Info0
 	),
 	proc_info_goal(ProcInfo0, Goal0),
-	traverse_goal(Goal0, Goal, Info1, Info2),
+	traverse_goal_2(Goal0, Goal, Info1, Info2),
 	fixup_proc_info(MustRecompute, Goal, Info2, Info).
 
 :- pred fixup_proc_info(bool::in, hlds_goal::in,
@@ -405,28 +405,28 @@
 	% The first time through the only predicate we can specialize
 	% is call/N. The pred_proc_id is that of the current procedure,
 	% used to find out which procedures need fixing up later.
-:- pred traverse_goal(hlds_goal::in, hlds_goal::out, 
+:- pred traverse_goal_2(hlds_goal::in, hlds_goal::out, 
 	higher_order_info::in, higher_order_info::out) is det.
 
-traverse_goal(conj(Goals0) - Info, conj(Goals) - Info) -->
-	list__map_foldl(traverse_goal, Goals0, Goals).
+traverse_goal_2(conj(Goals0) - Info, conj(Goals) - Info) -->
+	list__map_foldl(traverse_goal_2, Goals0, Goals).
 
-traverse_goal(par_conj(Goals0, SM) - Info, par_conj(Goals, SM) - Info) -->
+traverse_goal_2(par_conj(Goals0, SM) - Info, par_conj(Goals, SM) - Info) -->
 		% traverse_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.
 	traverse_disj(Goals0, Goals).
 
-traverse_goal(disj(Goals0, SM) - Info, disj(Goals, SM) - Info) -->
+traverse_goal_2(disj(Goals0, SM) - Info, disj(Goals, SM) - Info) -->
 	traverse_disj(Goals0, Goals).
 
 		% a switch is treated as a disjunction
-traverse_goal(switch(Var, CanFail, Cases0, SM) - Info,
+traverse_goal_2(switch(Var, CanFail, Cases0, SM) - Info,
 		switch(Var, CanFail, Cases, SM) - Info) -->
 	traverse_cases(Cases0, Cases).
 
 		% check whether this call could be specialized
-traverse_goal(Goal0, Goal) -->
+traverse_goal_2(Goal0, Goal) -->
 	{ Goal0 = generic_call(GenericCall, Args, _, _) - GoalInfo }, 
 	(
 		{
@@ -445,35 +445,35 @@
 	).
 
 		% check whether this call could be specialized
-traverse_goal(Goal0, Goal) -->
+traverse_goal_2(Goal0, Goal) -->
 	{ Goal0 = call(_,_,_,_,_,_) - _ }, 
 	maybe_specialize_call(Goal0, Goal).
 
 		% if-then-elses are handled as disjunctions
-traverse_goal(Goal0, Goal) -->
+traverse_goal_2(Goal0, Goal) -->
 	{ Goal0 = if_then_else(Vars, Cond0, Then0, Else0, SM) - GoalInfo },
 	get_pre_branch_info(PreInfo),
-	traverse_goal(Cond0, Cond),
-	traverse_goal(Then0, Then),
+	traverse_goal_2(Cond0, Cond),
+	traverse_goal_2(Then0, Then),
 	get_post_branch_info(PostThenInfo),
 	set_pre_branch_info(PreInfo),
-	traverse_goal(Else0, Else),
+	traverse_goal_2(Else0, Else),
 	get_post_branch_info(PostElseInfo),
 	{ Goal = if_then_else(Vars, Cond, Then, Else, SM) - GoalInfo },
 	{ merge_post_branch_infos(PostThenInfo, PostElseInfo, PostInfo) },
 	set_post_branch_info(PostInfo).
 
-traverse_goal(not(NegGoal0) - Info, not(NegGoal) - Info) -->
-	traverse_goal(NegGoal0, NegGoal).
+traverse_goal_2(not(NegGoal0) - Info, not(NegGoal) - Info) -->
+	traverse_goal_2(NegGoal0, NegGoal).
 
-traverse_goal(some(Vars, CanRemove, Goal0) - Info,
+traverse_goal_2(some(Vars, CanRemove, Goal0) - Info,
 		some(Vars, CanRemove, Goal) - Info) -->
-	traverse_goal(Goal0, Goal).
+	traverse_goal_2(Goal0, Goal).
 
-traverse_goal(Goal, Goal) -->
+traverse_goal_2(Goal, Goal) -->
 	{ Goal = pragma_c_code(_, _, _, _, _, _, _) - _ }.
 
-traverse_goal(Goal, Goal) -->
+traverse_goal_2(Goal, Goal) -->
 	{ Goal = unify(_, _, _, Unify, _) - _ }, 
 	check_unify(Unify).
 
@@ -491,7 +491,7 @@
 traverse_disj([], []) --> [].
 traverse_disj([Goal0 | Goals0], [Goal | Goals]) -->
 	get_pre_branch_info(PreInfo),
-	traverse_goal(Goal0, Goal),
+	traverse_goal_2(Goal0, Goal),
 	get_post_branch_info(PostInfo0),
 	traverse_disj_2(PreInfo, Goals0, Goals, PostInfo0, PostInfo),
 	set_post_branch_info(PostInfo).
@@ -504,7 +504,7 @@
 traverse_disj_2(PreInfo, [Goal0 | Goals0], [Goal | Goals],
 		PostInfo0, PostInfo) -->
 	set_pre_branch_info(PreInfo),
-	traverse_goal(Goal0, Goal),
+	traverse_goal_2(Goal0, Goal),
 	get_post_branch_info(PostInfo1),
 	{ merge_post_branch_infos(PostInfo0, PostInfo1, PostInfo2) },
 	traverse_disj_2(PreInfo, Goals0, Goals,
@@ -518,7 +518,7 @@
 traverse_cases([case(ConsId, Goal0) | Cases0],
 		[case(ConsId, Goal) | Cases]) -->
 	get_pre_branch_info(PreInfo),
-	traverse_goal(Goal0, Goal),
+	traverse_goal_2(Goal0, Goal),
 	get_post_branch_info(PostInfo0),
 	traverse_cases_2(PreInfo, Cases0, Cases, PostInfo0, PostInfo),
 	set_post_branch_info(PostInfo).
@@ -532,7 +532,7 @@
 		PostInfo0, PostInfo) -->
 	set_pre_branch_info(PreInfo),
 	{ Case0 = case(ConsId, Goal0) },
-	traverse_goal(Goal0, Goal),
+	traverse_goal_2(Goal0, Goal),
 	{ Case = case(ConsId, Goal) },
 	get_post_branch_info(PostInfo1),
 	{ merge_post_branch_infos(PostInfo0, PostInfo1, PostInfo2) },
@@ -1174,6 +1174,11 @@
 				% list.
 	).
 
+	% WARNING - do not filter out higher-order arguments from the
+	% request returned by find_matching_version, otherwise some
+	% type-infos that the call specialization code is expecting to
+	% come from the curried arguments of the higher-order arguments
+	% will not be present in the specialized argument list.
 :- pred find_matching_version(higher_order_info::in, 
 	pred_id::in, proc_id::in, list(prog_var)::in, prog_context::in,
 	list(higher_order_arg)::in, bool::in, find_result::out) is det.
@@ -1272,10 +1277,12 @@
 		% Work out which type variables don't already have type-infos
 		% in the list of argument types.
 		% The list is in the order which the type variables occur
-		% in the list of argument types to avoid problems ordering
-		% the extra type-info arguments in calls to imported
-		% user-guided type specialization procedures (that is also
-		% why `goal_util__extra_nonlocal_typeinfos' is not used here).
+		% in the list of argument types so that the extra type-info
+		% arguments for calls to imported user-guided type
+		% specialization procedures can be matched against the
+		% specialized version (`goal_util__extra_nonlocal_typeinfos'
+		% is not used here because the type variables are returned
+		% sorted by variable number, which will vary between calls).
 		Info = info(_, _, _, _, _, ProcInfo, _, _, _),
 		proc_info_vartypes(ProcInfo, VarTypes),
 		map__apply_to_list(Args1, VarTypes, ArgTypes),
@@ -1632,9 +1639,8 @@
 		% This could possibly be better handled by just inlining 
 		% the unification code, but the compiler doesn't have the
 		% code for the comparison or in-in unification procedures
-		% for imported types, and Tyson has been talking for ages
-		% about doing generic unification and comparison in C code in
-		% the runtime system. 
+		% for imported types, and unification and comparison will
+		% eventually be implemented in C code in the runtime system. 
 		( SpecialId = unify ; SpecialId = compare ),
 		type_constructors(SpecialPredType, ModuleInfo, Constructors),
 		type_is_no_tag_type(Constructors, Constructor, WrappedType),
@@ -2052,7 +2058,7 @@
 	map__init(PredVars0),
 	Info0 = info(PredVars0, Requests0, NewPreds, PredProcId,
 			PredInfo0, ProcInfo0, ModuleInfo0, Params, unchanged),
-	traverse_goal_0(MustRecompute, Info0, Info),
+	traverse_goal(MustRecompute, Info0, Info),
 	Info = info(_, Requests1, _, _, PredInfo, ProcInfo, ModuleInfo1, _, _),
 	module_info_set_pred_proc_info(ModuleInfo1, PredProcId, PredInfo,
 		ProcInfo, ModuleInfo2),
--- make_hlds.m	1999/10/01 02:11:03	1.1
+++ make_hlds.m	1999/10/01 04:02:08
@@ -1003,7 +1003,7 @@
 	->
 	    { error("handle_pragma_type_spec_subst: empty substitution") }
 	;
-	    { multiple_subst_vars(VarsToSub, MultiSubstVars0) },
+	    { find_duplicate_list_elements(VarsToSub, MultiSubstVars0) },
 	    { MultiSubstVars0 \= [] }
 	->
     	    { list__sort_and_remove_dups(MultiSubstVars0, MultiSubstVars) },
@@ -1109,12 +1109,12 @@
 	    )
 	).
 
-:- pred multiple_subst_vars(list(T), list(T)).
-:- mode multiple_subst_vars(in, out) is det.
+:- pred find_duplicate_list_elements(list(T), list(T)).
+:- mode find_duplicate_list_elements(in, out) is det.
 
-multiple_subst_vars([], []).
-multiple_subst_vars([H | T], Vars) :-
-	multiple_subst_vars(T, Vars0),
+find_duplicate_list_elements([], []).
+find_duplicate_list_elements([H | T], Vars) :-
+	find_duplicate_list_elements(T, Vars0),
 	( list__member(H, T) ->
 		Vars = [H | Vars0]
 	;
--- polymorphism.m	1999/10/01 02:09:25	1.1
+++ polymorphism.m	1999/10/01 04:02:24
@@ -926,13 +926,6 @@
 		ExtraTypeClassUnifyGoals),
 	
 	%
-	% figure out the list of universally quantified type variables
-	%
-	%term__vars_list(ArgTypes, HeadTypeVars0),
-	%list__remove_dups(HeadTypeVars0, HeadTypeVars),
-	%list__delete_elems(HeadTypeVars, ExistQVars, UnivQTVars),
-
-	%
 	% apply the type bindings to the unconstrained type variables
 	% to give the actual types, and then generate code
 	% to initialize the type_infos for those types
--------------------------------------------------------------------------
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