[m-rev.] for review: untupling transformation

Julien Fischer juliensf at cs.mu.OZ.AU
Tue Feb 1 12:28:17 AEDT 2005


On Mon, 31 Jan 2005, Peter Wang wrote:

> For review by anyone.
>
> Estimated hours taken: 80
> Branches: main
>
> This change adds a --untuple option to the compiler which invokes a new
> transformation pass.  The transformation takes an HLDS structure as its
s/an HLDS/the HLDS/

> input and transforms the locally-defined procedures as follows: if the
> formal parameter of a procedure has a type consisting of a single function
> symbol then that parameter is expanded into multiple parameters (one for
> each field of the functor).  Tuple types are also expanded.  The argument
> lists are expanded as deeply (flatly) as possible.  Calls within the
> same module are updated to use the new versions of the procedures.
>

The log message should say where/why this transformation will be useful.

> compiler/untupling.m:
> 	New file.
>
> compiler/transform_hlds.m:
> 	Add the new untupling submodule to the transform_hlds module.
>
> compiler/handle_options.m:
> compiler/options.m:
> 	Add a new boolean option --untuple to the compiler.
>
> compiler/mercury_compile.m:
> 	Add code to run the untupling pass if the --untuple option is given.
>
> compiler/hlds_pred.m:
> compiler/layout_out.m:
> 	Add a untuple constructor to the pred_transformation type.
>
> 	Add a untuple_proc_info field to proc_sub_info and associated
> 	predicates proc_info_get_maybe_untuple_info and
> 	proc_info_set_maybe_untuple_info.
>
> compiler/hlds_out.m:
> 	Add code to print out the information stored in the
> 	untuple_proc_info field of proc_sub_info.
>
> compiler/hlds_goal.m:
> 	Add new utility predicates construct_functor and deconstruct_functor
> 	for creating construct and deconstruct unification goals.
>
> 	Make construct_tuple and deconstruct_tuple be special cases of
> 	construct_functor and deconstruct_functor, respectively.
>
>

> Index: compiler/options.m
> ===================================================================
> RCS file: /home/mercury1/repository/mercury/compiler/options.m,v
> retrieving revision 1.441
> diff -u -r1.441 options.m
> --- compiler/options.m	27 Jan 2005 03:38:09 -0000	1.441
> +++ compiler/options.m	31 Jan 2005 02:58:38 -0000
> @@ -491,6 +491,7 @@
>  		;	termination_error_limit
>  		;	termination_path_limit
>  		;	analyse_exceptions
> +		;	untuple
>  	%	- HLDS->LLDS
>  		;	smart_indexing
>  		;	  dense_switch_req_density
> @@ -1099,6 +1100,7 @@
>  	deforestation_cost_factor	-	int(1000),
>  	deforestation_vars_threshold 	-	int(200),
>  	deforestation_size_threshold 	-	int(15),
> +	untuple			- 	bool(no),
>
>  % HLDS -> LLDS
>  	smart_indexing		-	bool(no),
> @@ -1767,6 +1769,7 @@
>  long_option("termination-path-limit",	termination_path_limit).
>  long_option("term-path-limit",		termination_path_limit).
>  long_option("analyse-exceptions", 	analyse_exceptions).
> +long_option("untuple",			untuple).
>
>  % HLDS->LLDS optimizations
>  long_option("smart-indexing",		smart_indexing).

You should add this new option to the help message (commented out
at the moment), and similarly to the user guide.

> Index: compiler/untupling.m
> ===================================================================
> RCS file: compiler/untupling.m
> diff -N compiler/untupling.m
> --- /dev/null	1 Jan 1970 00:00:00 -0000
> +++ compiler/untupling.m	31 Jan 2005 04:30:18 -0000
> @@ -0,0 +1,689 @@
> +%-----------------------------------------------------------------------------%
> +% Copyright (C) 2005 The University of Melbourne.
> +% This file may only be copied under the terms of the GNU General
> +% Public License - see the file COPYING in the Mercury distribution.
> +%-----------------------------------------------------------------------------%
> +%
> +% File: untupling.m.
> +%
> +% Author: wangp.
> +%
> +% This module takes an HLDS structure as its input and transforms the

I would rewrite that as:

	This module takes the HLDS and transforms ....

> +% locally-defined procedures as follows: if the formal parameter of a
> +% procedure has a type consisting of a single function symbol then that
> +% parameter is expanded into multiple parameters (one for each field of the
> +% functor).  Tuple types are also expanded.  The argument lists are expanded
> +% as deeply (flatly) as possible.
> +%
> +% e.g. for the following module,
s/module/predicate/

> +%
> +%	:- type t ---> t(u).
> +%	:- type u ---> u(v, w).
> +%	:- type v ---> v1 ; v2.
> +%	:- type w ---> w(int, string).
> +%
> +%	:- pred f(t::in) is det.
> +%	f(T) :- blah.
> +%
> +% a transformed version of f/1 would be added:
> +%
> +%	:- pred f_untupled(v::in, int::in, string::in) is det.
> +%	f_untupled(V, W1, W2) :- blah.
> +%
> +% After all the procedures have been processed in that way, a second pass is
> +% made to update all the calls in the module which refer to the old procedures
> +% to call the transformed procedures.  This is done by adding deconstruction
> +% and construction unifications as needed, which can later be simplified by a
> +% simplification pass.
> +%
Are the simplifications done in this module or are they done
eleswhere?

> +%-----------------------------------------------------------------------------%
> +
> +:- module transform_hlds__untupling.
> +
> +:- interface.
> +
> +:- import_module hlds__hlds_module.
> +
> +:- import_module io.
> +
> +:- pred untuple_arguments(module_info::in, module_info::out, io::di, io::uo)
> +	is det.
> +
> +%-----------------------------------------------------------------------------%
> +
> +:- implementation.
> +
> +:- import_module check_hlds__det_analysis.
> +:- import_module check_hlds__mode_util.
> +:- import_module hlds__hlds_data.
> +:- import_module hlds__hlds_goal.
> +:- import_module hlds__hlds_pred.
> +:- import_module hlds__quantification.
> +:- import_module mdbcomp__prim_data.
> +:- import_module parse_tree__error_util.
> +:- import_module parse_tree__prog_data.
> +:- import_module parse_tree__prog_mode.
> +:- import_module parse_tree__prog_type.
> +:- import_module parse_tree__prog_util.
> +
> +:- import_module bool, list, map, require, std_util, string, svmap.
> +:- import_module svvarset, term, varset.
> +
> +	% The transform_map structure records which procedures were
> +	% transformed into what procedures during the first pass.
> +	%
> +:- type transform_map == map(pred_proc_id, transformed_proc).
> +
> +:- type transformed_proc
> +	--->	transformed_proc(
> +			pred_proc_id,
> +				% The predicate and procedure that the old
> +				% procedure was transformed into.

I suggest rewording that comment as:

	A procedure that was generated by the
	untupling transformation.

> +			hlds_goal
> +				% A call goal template that is used to update
> +				% calls refering to the old procedure to the
> +				% new procedure.

s/refering/referring/

> +		).
> +
> +untuple_arguments(!ModuleInfo, !IO) :-
> +	expand_args_in_module(!ModuleInfo, TransformMap),
> +	fix_calls_to_expanded_procs(TransformMap, !ModuleInfo).
> +
> +%-----------------------------------------------------------------------------%
> +%-----------------------------------------------------------------------------%
> +

Add a section heading here (see the coding standard)

	%--------------------------------....
	%
	% Pass 1
	%


> +	% This is the top level of the first pass.  It expands procedure
> +	% arguments where possible, adding new versions of the transformed
> +	% procedures into the module and recording the mapping between the old
> +	% and new procedures in the transform map.
> +	%
> +:- pred expand_args_in_module(module_info::in, module_info::out,
> +	transform_map::out) is det.
> +
> +expand_args_in_module(!ModuleInfo, TransformMap) :-
> +	module_info_predids(!.ModuleInfo, PredIds),
> +	list__foldl2(expand_args_in_pred, PredIds,
> +		!ModuleInfo, map__init, TransformMap).
> +
> +:- pred expand_args_in_pred(pred_id::in, module_info::in, module_info::out,
> +	transform_map::in, transform_map::out) is det.
> +
> +expand_args_in_pred(PredId, !ModuleInfo, !TransformMap) :-
> +	module_info_types(!.ModuleInfo, TypeTable),
> +	module_info_pred_info(!.ModuleInfo, PredId, PredInfo),
> +	(
> +		% Only perform the transformation on predicates which
> +		% satisfy the following criteria.
Is it possible that some of the restrictions below could eventually
be lifted?  If so, you should mention this.

> +		pred_info_import_status(PredInfo, local),
> +		pred_info_get_goal_type(PredInfo, clauses),
> +		pred_info_get_exist_quant_tvars(PredInfo, []),
> +		pred_info_get_head_type_params(PredInfo, []),
> +		pred_info_get_class_context(PredInfo, constraints([], [])),
> +		pred_info_get_origin(PredInfo, user(_)),
> +		pred_info_arg_types(PredInfo, TypeVarSet, ExistQVars,
> +			ArgTypes),
> +		varset__is_empty(TypeVarSet),
> +		ExistQVars = [],
> +		at_least_one_expandable_type(ArgTypes, TypeTable)
> +	->
> +		ProcIds = pred_info_non_imported_procids(PredInfo),
> +		list__foldl2(expand_args_in_proc(PredId), ProcIds,
> +			!ModuleInfo, !TransformMap)
> +	;
> +		true
> +	).
> +
> +:- pred at_least_one_expandable_type(list(type)::in, type_table::in)
> +	is semidet.
> +
> +at_least_one_expandable_type([Type | Types], TypeTable) :-
> +	( expand_type(Type, TypeTable, yes(_))
> +	; at_least_one_expandable_type(Types, TypeTable)
> +	).
> +
> +%-----------------------------------------------------------------------------%
> +
> +	% This structure records the mapping between a head variable of the
> +	% original procedure, and the list of variables that it was finally
> +	% expanded into.  If the head variable expands into some intermediate
> +	% variables which are then expanded further, the intermediate
> +	% variables are not listed in the mapping.
> +	%
> +:- type untuple_map == map(prog_var, prog_vars).
> +
> +:- pred expand_args_in_proc(pred_id::in, proc_id::in, module_info::in,
> +	module_info::out, transform_map::in, transform_map::out) is det.
> +
> +expand_args_in_proc(PredId, ProcId, !ModuleInfo, !TransformMap) :-
> +	some [!ProcInfo] (
> +		module_info_types(!.ModuleInfo, TypeTable),
> +		module_info_pred_proc_info(!.ModuleInfo, PredId, ProcId,
> +			PredInfo0, !:ProcInfo),
> +
> +		proc_info_headvars(!.ProcInfo, HeadVars0),
> +		proc_info_argmodes(!.ProcInfo, ArgModes0),
> +		proc_info_goal(!.ProcInfo, Goal0),
> +		proc_info_vartypes(!.ProcInfo, VarTypes0),
> +		proc_info_varset(!.ProcInfo, VarSet0),
> +
> +		expand_args_in_proc_2(HeadVars0, ArgModes0, HeadVars, ArgModes,
> +			Goal0, Goal, VarSet0, VarSet, VarTypes0, VarTypes,
> +			TypeTable, UntupleMap),
> +
> +		proc_info_set_headvars(HeadVars, !ProcInfo),
> +		proc_info_set_argmodes(ArgModes, !ProcInfo),
> +		proc_info_set_goal(Goal, !ProcInfo),
> +		proc_info_set_varset(VarSet, !ProcInfo),
> +		proc_info_set_vartypes(VarTypes, !ProcInfo),
> +		requantify_proc(!ProcInfo),
> +		recompute_instmap_delta_proc(yes, !ProcInfo, !ModuleInfo),
> +
> +		create_aux_pred(PredId, ProcId, PredInfo0, !.ProcInfo,
> +			AuxPredId, AuxProcId, CallAux,
> +			AuxPredInfo, AuxProcInfo0, !ModuleInfo),
> +		proc_info_set_maybe_untuple_info(
> +			yes(untuple_proc_info(UntupleMap)),
> +			AuxProcInfo0, AuxProcInfo),
> +		module_info_set_pred_proc_info(AuxPredId, AuxProcId,
> +			AuxPredInfo, AuxProcInfo, !ModuleInfo),
> +		svmap__det_insert(proc(PredId, ProcId),
> +			transformed_proc(proc(AuxPredId, AuxProcId), CallAux),
> +			!TransformMap)
> +	).
> +
> +:- pred expand_args_in_proc_2(prog_vars::in, list(mode)::in,
> +	prog_vars::out, list(mode)::out, hlds_goal::in, hlds_goal::out,
> +	prog_varset::in, prog_varset::out, vartypes::in, vartypes::out,
> +	type_table::in, untuple_map::out) is det.
> +
> +expand_args_in_proc_2(HeadVars0, ArgModes0, HeadVars, ArgModes,
> +		!Goal, !VarSet, !VarTypes, TypeTable, UntupleMap) :-
> +	expand_args_in_proc_3(HeadVars0, ArgModes0, ListOfHeadVars,
> +		ListOfArgModes, !Goal, !VarSet, !VarTypes, TypeTable),
> +	list__condense(ListOfHeadVars, HeadVars),
> +	list__condense(ListOfArgModes, ArgModes),
> +	build_untuple_map(HeadVars0, ListOfHeadVars, map__init, UntupleMap).
> +

> +	Origin = transformed(untuple(ProcNo), OrigOrigin, PredId),
> +	hlds_pred__define_new_pred(
> +		Origin,			% in
> +		Goal,			% in
> +		CallAux,		% out
> +		AuxHeadVars,		% in
> +		_ExtraArgs,		% out
> +		InitialAuxInstMap,	% in
> +		AuxPredName,		% in
> +		TVarSet,		% in
> +		VarTypes,		% in
> +		ClassContext,		% in
> +		TVarMap,		% in
> +		TCVarMap,		% in
> +		VarSet,			% in
> +		InstVarSet,		% in
> +		Markers,		% in
> +		Owner,			% in
> +		address_is_not_taken,	% in
> +		ModuleInfo0,
> +		ModuleInfo,
> +		proc(AuxPredId, AuxProcId)
> +					% out
> +	),
The mode annotations in comments are not really necessary here.

> +%-----------------------------------------------------------------------------%
> +%-----------------------------------------------------------------------------%
Add a section heading here.

> +
> +	% This is the top level of the second pass.  It takes the transform
> +	% map built during the first pass as input.  For every call to a
> +	% procedure in the transform map, it rewrites the call to use the new
> +	% procedure instead, inserting unifications before and after the call
> +	% as necessary.
> +	%
> +:- pred fix_calls_to_expanded_procs(transform_map::in, module_info::in,
> +	module_info::out) is det.
> +
> +fix_calls_to_expanded_procs(TransformMap, !ModuleInfo) :-
> +	module_info_predids(!.ModuleInfo, PredIds),
> +	list__foldl(fix_calls_in_pred(TransformMap), PredIds, !ModuleInfo).
> +
> +:- pred fix_calls_in_pred(transform_map::in, pred_id::in, module_info::in,
> +	module_info::out) is det.
> +
> +fix_calls_in_pred(TransformMap, PredId, !ModuleInfo) :-
> +	module_info_pred_info(!.ModuleInfo, PredId, PredInfo),
> +	ProcIds = pred_info_non_imported_procids(PredInfo),
> +	list__foldl(fix_calls_in_proc(TransformMap, PredId), ProcIds,
> +		!ModuleInfo).
> +
> +:- pred fix_calls_in_proc(transform_map::in, pred_id::in, proc_id::in,
> +	module_info::in, module_info::out) is det.
> +
> +fix_calls_in_proc(TransformMap, PredId, ProcId, !ModuleInfo) :-
> +	some [!ProcInfo] (
> +		module_info_pred_proc_info(!.ModuleInfo, PredId, ProcId,
> +			PredInfo, !:ProcInfo),
> +		proc_info_goal(!.ProcInfo, Goal0),
> +		proc_info_vartypes(!.ProcInfo, VarTypes0),
> +		proc_info_varset(!.ProcInfo, VarSet0),
> +		fix_calls_in_goal(Goal0, Goal, VarSet0, VarSet,
> +			VarTypes0, VarTypes, TransformMap, !.ModuleInfo),
> +		( Goal0 \= Goal ->
> +			proc_info_set_goal(Goal, !ProcInfo),
> +			proc_info_set_varset(VarSet, !ProcInfo),
> +			proc_info_set_vartypes(VarTypes, !ProcInfo),
> +			requantify_proc(!ProcInfo),
> +			recompute_instmap_delta_proc(yes, !ProcInfo,
> +				!ModuleInfo),
> +			module_info_set_pred_proc_info(PredId, ProcId,
> +				PredInfo, !.ProcInfo, !ModuleInfo)
> +		;
> +			true
> +		)
> +	).
> +
> +%-----------------------------------------------------------------------------%
> +
> +:- pred fix_calls_in_goal(hlds_goal::in, hlds_goal::out, prog_varset::in,
> +	prog_varset::out, vartypes::in, vartypes::out, transform_map::in,
> +	module_info::in) is det.
> +
> +fix_calls_in_goal(Goal - GoalInfo, Goal - GoalInfo, !_, !_, _, _) :-
> +	Goal = foreign_proc(_, _, _, _, _, _).
> +
> +fix_calls_in_goal(Goal - GoalInfo, Goal - GoalInfo, !_, !_, _, _) :-
> +	Goal = generic_call(_, _, _, _).
> +
> +fix_calls_in_goal(Goal0 - GoalInfo0, Goal, !VarSet, !VarTypes,
> +		TransformMap, ModuleInfo) :-
> +	Goal0 = call(CalleePredId, CalleeProcId, OrigArgs, _, _, _),
> +	(
> +		map__search(TransformMap,
> +			proc(CalleePredId, CalleeProcId),
> +			transformed_proc(_, CallAux0 - CallAuxInfo))
> +	->
> +		module_info_types(ModuleInfo, TypeTable),
> +		module_info_pred_proc_info(ModuleInfo, CalleePredId,
> +			CalleeProcId, _CalleePredInfo, CalleeProcInfo),
> +		proc_info_argmodes(CalleeProcInfo, OrigArgModes),
> +		expand_call_args(OrigArgs, OrigArgModes, Args,
> +			EnterUnifs, ExitUnifs, !VarSet, !VarTypes, TypeTable),
> +		(
> +			CallAux = CallAux0 ^ call_args := Args
> +		->
> +			Call = CallAux - CallAuxInfo,
> +			ConjList = EnterUnifs ++ [Call] ++ ExitUnifs,
> +			conj_list_to_goal(ConjList, GoalInfo0, Goal)
> +		;
> +			unexpected(this_file,
> +				"fix_calls_in_goal: not a call template")
> +		)
> +	;
> +		Goal = Goal0 - GoalInfo0
> +	).
> +
> +fix_calls_in_goal(Goal - GoalInfo, Goal - GoalInfo, !_, !_, _, _) :-
> +	Goal = unify(_, _, _, _, _).
> +
> +fix_calls_in_goal(not(Goal0) - GoalInfo, not(Goal) - GoalInfo,
> +		!VarSet, !VarTypes, TransformMap, ModuleInfo) :-
> +	fix_calls_in_goal(Goal0, Goal, !VarSet, !VarTypes, TransformMap,
> +		ModuleInfo).
> +
> +fix_calls_in_goal(some(Vars, CanRemove, Goal0) - GoalInfo,
> +		some(Vars, CanRemove, Goal) - GoalInfo,
> +		!VarSet, !VarTypes, TransformMap, ModuleInfo) :-
> +	fix_calls_in_goal(Goal0, Goal, !VarSet, !VarTypes, TransformMap,
> +		ModuleInfo).
> +
> +fix_calls_in_goal(conj(Goals0) - GoalInfo, conj(Goals) - GoalInfo,
> +		!VarSet, !VarTypes, TransformMap, ModuleInfo) :-
> +	fix_calls_in_conj(Goals0, Goals, !VarSet, !VarTypes, TransformMap,
> +		ModuleInfo).
> +
> +fix_calls_in_goal(par_conj(Goals0) - GoalInfo, par_conj(Goals) - GoalInfo,
> +		!VarSet, !VarTypes, TransformMap, ModuleInfo) :-
> +	fix_calls_in_par_conj(Goals0, Goals, !VarSet, !VarTypes,
> +		TransformMap, ModuleInfo).
> +
> +fix_calls_in_goal(disj(Goals0) - GoalInfo, disj(Goals) - GoalInfo,
> +		!VarSet, !VarTypes, TransformMap, ModuleInfo) :-
> +	fix_calls_in_disj(Goals0, Goals, !VarSet, !VarTypes, TransformMap,
> +		ModuleInfo).
> +
> +fix_calls_in_goal(switch(Var, CanFail, Cases0) - GoalInfo,
> +		switch(Var, CanFail, Cases) - GoalInfo,
> +		!VarSet, !VarTypes, TransformMap, ModuleInfo) :-
> +	fix_calls_in_cases(Cases0, Cases, !VarSet, !VarTypes, TransformMap,
> +		ModuleInfo).
> +
> +fix_calls_in_goal(if_then_else(Vars, Cond0, Then0, Else0) - GoalInfo,
> +		if_then_else(Vars, Cond, Then, Else) - GoalInfo,
> +		!VarSet, !VarTypes, TransformMap, ModuleInfo) :-
> +	fix_calls_in_goal(Cond0, Cond, !VarSet, !VarTypes, TransformMap,
> +		ModuleInfo),
> +	fix_calls_in_goal(Then0, Then, !VarSet, !VarTypes, TransformMap,
> +		ModuleInfo),
> +	fix_calls_in_goal(Else0, Else, !VarSet, !VarTypes, TransformMap,
> +		ModuleInfo).
> +
> +fix_calls_in_goal(shorthand(_) - _, _, !_, !_, _, _) :-
> +	unexpected(this_file, "fix_calls_in_goal: unexpected shorthand").
> +
> +%-----------------------------------------------------------------------------%
> +
> +:- pred fix_calls_in_conj(hlds_goals::in, hlds_goals::out, prog_varset::in,
> +	prog_varset::out, vartypes::in, vartypes::out, transform_map::in,
> +	module_info::in) is det.
> +
> +fix_calls_in_conj([], [], !VarSet, !VarTypes, _, _).
> +fix_calls_in_conj([Goal0 | Goals0], Goals, !VarSet, !VarTypes, TransformMap,
> +		ModuleInfo) :-
> +	fix_calls_in_goal(Goal0, Goal1, !VarSet, !VarTypes, TransformMap,
> +		ModuleInfo),
> +	fix_calls_in_conj(Goals0, Goals1, !VarSet, !VarTypes, TransformMap,
> +		ModuleInfo),
> +	(if Goal1 = conj(ConjGoals) - _ then
> +		Goals = ConjGoals ++ Goals1
> +	else
> +		Goals = [Goal1 | Goals1]
> +	).
> +
> +:- pred fix_calls_in_par_conj(hlds_goals::in, hlds_goals::out,
> +	prog_varset::in, prog_varset::out, vartypes::in, vartypes::out,
> +	transform_map::in, module_info::in) is det.
> +
> +fix_calls_in_par_conj([], [], !VarSet, !VarTypes, _, _).
> +fix_calls_in_par_conj([Goal0 | Goals0], [Goal | Goals], !VarSet, !VarTypes,
> +		TransformMap, ModuleInfo) :-
> +	fix_calls_in_goal(Goal0, Goal, !VarSet, !VarTypes, TransformMap,
> +		ModuleInfo),
> +	fix_calls_in_par_conj(Goals0, Goals, !VarSet, !VarTypes, TransformMap,
> +		ModuleInfo).
> +
> +:- pred fix_calls_in_disj(hlds_goals::in, hlds_goals::out, prog_varset::in,
> +	prog_varset::out, vartypes::in, vartypes::out, transform_map::in,
> +	module_info::in) is det.
> +
> +fix_calls_in_disj([], [], !VarSet, !VarTypes, _, _).
> +fix_calls_in_disj([Goal0 | Goals0], [Goal | Goals], !VarSet, !VarTypes,
> +		TransformMap, ModuleInfo) :-
> +	fix_calls_in_goal(Goal0, Goal, !VarSet, !VarTypes, TransformMap,
> +		ModuleInfo),
> +	fix_calls_in_disj(Goals0, Goals, !VarSet, !VarTypes, TransformMap,
> +		ModuleInfo).
> +
> +:- pred fix_calls_in_cases(list(case)::in, list(case)::out, prog_varset::in,
> +	prog_varset::out, vartypes::in, vartypes::out, transform_map::in,
> +	module_info::in) is det.
> +
> +fix_calls_in_cases([], [], !VarSet, !VarTypes, _, _).
> +fix_calls_in_cases([Case0 | Cases0], [Case | Cases], !VarSet, !VarTypes,
> +		TransformMap, ModuleInfo) :-
> +	Case0 = case(Functor, Goal0),
> +	fix_calls_in_goal(Goal0, Goal, !VarSet, !VarTypes, TransformMap,
> +		ModuleInfo),
> +	Case = case(Functor, Goal),
> +	fix_calls_in_cases(Cases0, Cases, !VarSet, !VarTypes, TransformMap,
> +		ModuleInfo).
> +
> +%-----------------------------------------------------------------------------%
> +
> +:- pred expand_call_args(prog_vars::in, list(mode)::in, prog_vars::out,
> +	hlds_goals::out, hlds_goals::out, prog_varset::in, prog_varset::out,
> +	vartypes::in, vartypes::out, type_table::in) is det.
> +
> +expand_call_args([], [], [], [], [], !VarSet, !VarTypes, _).
> +expand_call_args([Arg0 | Args0], [ArgMode | ArgModes], Args,
> +		EnterUnifs, ExitUnifs, !VarSet, !VarTypes, TypeTable) :-
> +	map__lookup(!.VarTypes, Arg0, Arg0Type),
> +	(
> +		expand_argument(ArgMode, Arg0Type, TypeTable,
> +			yes(ConsId - Types))
> +	->
> +		NumVars = list__length(Types),
> +		svvarset__new_vars(NumVars, ReplacementArgs, !VarSet),
> +		svmap__det_insert_from_corresponding_lists(
> +			ReplacementArgs, Types, !VarTypes),
> +		list__duplicate(NumVars, ArgMode, ReplacementModes),
> +		( ArgMode = in_mode ->
> +			deconstruct_functor(Arg0, ConsId,
> +				ReplacementArgs, Unif),
> +			EnterUnifs = [Unif | EnterUnifs1],
> +			expand_call_args(ReplacementArgs ++ Args0,
> +				ReplacementModes ++ ArgModes,
> +				Args, EnterUnifs1, ExitUnifs,
> +				!VarSet, !VarTypes, TypeTable)
> +		; ArgMode = out_mode ->
> +			construct_functor(Arg0, ConsId,
> +				ReplacementArgs, Unif),
> +			ExitUnifs = ExitUnifs1 ++ [Unif],
> +			expand_call_args(ReplacementArgs ++ Args0,
> +				ReplacementModes ++ ArgModes,
> +				Args, EnterUnifs, ExitUnifs1,
> +				!VarSet, !VarTypes, TypeTable)
> +		;
> +			unexpected(this_file,
> +				"expand_call_args: unsupported mode")
> +		)
> +	;
> +		Args = [Arg0 | Args1],
> +		expand_call_args(Args0, ArgModes, Args1, EnterUnifs,
> +			ExitUnifs, !VarSet, !VarTypes, TypeTable)
> +	).
> +
> +expand_call_args([], [_|_], _, _, _, !_, !_, _) :-
> +	unexpected(this_file, "expand_call_args: length mismatch").
> +expand_call_args([_|_], [], _, _, _, !_, !_, _) :-
> +	unexpected(this_file, "expand_call_args: length mismatch").
> +
> +%-----------------------------------------------------------------------------%
> +%-----------------------------------------------------------------------------%
> +
> +	% expand_argument(ArgMode, ArgType, TypeTable, MaybeConsIdAndTypes)
> +	% This predicate tries to expand the argument of the given mode and
> +	% type.  If this is possible then MaybeConsIdAndTypes is unified with
> +	% a pair consisting of the cons_id of the constructor which was
> +	% expanded and the types for that constructor.
> +	%
s/the types/the types of the arguments/

> +:- pred expand_argument((mode)::in, (type)::in, type_table::in,
> +	maybe(pair(cons_id, list(type)))::out) is det.
> +
> +expand_argument(ArgMode, ArgType, TypeTable, MaybeConsIdAndTypes) :-
> +	( expandable_arg_mode(ArgMode) ->
> +		expand_type(ArgType, TypeTable, MaybeConsIdAndTypes)
> +	;
> +		MaybeConsIdAndTypes = no
> +	).
> +
> +	% This module so far only knows how to expand arguments which have
> +	% the following modes.
> +	%
You should have list of current limitations of this module at the head
of the file - this should be listed among them.

> +:- pred expandable_arg_mode((mode)::in) is semidet.
> +
> +expandable_arg_mode(in_mode).
> +expandable_arg_mode(out_mode).
> +

Does this compiler bootstrap when this transformation is turned on?

That's all for now,

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