[m-rev.] For review: Annotate the HLDS with regions

Julien Fischer juliensf at csse.unimelb.edu.au
Thu Jul 5 16:48:53 AEST 2007


On Fri, 29 Jun 2007, Quan Phan wrote:

> Estimated hours taken: 48.
> Branch: main.
>
> Annotate the HLDS with information about region information. This includes:
> - Adding calls to region builtins, which are defined in
> library/region_builtin.m, currently they are methods for creating and
> removing regions.
> - Adding extra region arguments for procedures and calls, so that regions can
> be passed between procedure calls. The extra region arguments are appended at
> the end of the argument list for predicates. For functions, we make sure that
> the output argument is always at the last so they are added before the last.
> - Annotating construction unifications with regions so that terms can be
> constructed in regions. The changes here must be consistent with the changes
> necessary in unify_gen.m (which will be posted in another email). This means
> that we will only update constructions of terms which are actually stored on
> the heap.

I suggest rewriting as follows:

 	Add an HLDS->HLDS transformation that implements region-based
 	memory management.  This involves:

 		- adding calls to the region builtin predicates for
 		  creating and removing regions.

 		- add extra region arguments to procedure arguments
   		  and call sites.

 		- annotating construction unifications with information
 	          about which region a term should be constructed in.

> After the region transformation each procedure needs to be requantified. After
> ALL the procedures have been transformed and requantified, instmap delta is
> recomputed and purity is rechecked. That is necessary because requantification
> and repurity check lookup information about the transformed procedures.

I would not include that last paragraph in the log message.

> The annotated HLDS can be viewed by compiling with --dump-hlds=240.
>
> compiler/hlds_goal.m:
>        Add another type constructor for how_to_construct to allow
> 	constructing terms in regions.
>
> compiler/goal_util.m
> compiler/hlds_out.m
> compiler/ml_unify_gen.m
> compiler/interval.m
> compiler/structure_reuse.indirect.m
> 	Simple change to suit with the above additional type constructor.
>
> compiler/quantification.m
> 	Change to suit with the additional type constructor. The (region)
> 	variable in construct_in_region is considered nonlocal to the
> 	construction.

I wouldn't include that last sentence in the log message.

>
> compiler/rbmm.condition_renaming.m:
> 	Change the algorithm so that the transformation needed to solve the
> 	problem with if-then-else is derived after the region annotated
> 	program has been transformed for solving the region resurrection
> 	problem. This is needed because the solution to region resurrection
> 	problem may introduce bindings of non-local region variables inside
> 	condition goal of an if-then-else.

 	... inside the conditions of if-then-elses.

> compiler/rbmm.execution_path.m:
> 	Correct a typo.
>
> compiler/rbmm.m:
> 	Add a new submodule region_transformation.
> 	Call to region_transform to actually update the HLDS with region
> 	information.
>
> compiler/rbmm.region_resurrection_renaming.m:
> 	Provide better comments. Reordering some predicates to suit with
> 	the flow of computation.
>
> compiler/rbmm.region_transformation.m:
> 	New file.
> 	Annotate the HLDS with region information to prepare for code
> 	generation.

This addition of this module is the major piece of work in this change,
so this should be listed first.  Also, I would say transform rather
than annotate.

> compiler/rbmm.actual_region_arguments.m:
> 	Change the data structure so that the actual region arguments are
> 	separated into "in" and "out" groups.

What data structure?

In future could you please use the interdiff program to create a relative
diff between your original diff and the revised one.

...

> Index: rbmm.condition_renaming.m
> ===================================================================
> RCS file:
> /home/mercury/mercury1/repository/mercury/compiler/rbmm.condition_renaming.m,v
> retrieving revision 1.2
> diff -u -u -r1.2 rbmm.condition_renaming.m
> --- rbmm.condition_renaming.m	15 Jun 2007 11:46:11 -0000	1.2
> +++ rbmm.condition_renaming.m	27 Jun 2007 06:05:22 -0000
> @@ -16,6 +16,17 @@
> % program point so that the binding of non-local regions in the condition
> % goal of an if-then-else is resolved.
> %
> +% When reasoning about the renaming and reverse renaming needed for
> +% an if-then-else here we take into account the changes to regions caused
> +% by the renaming and renaming annotations needed for region resurrection.
> +% This can be viewed as if the program is transformed by the renaming
> +% and reverse renaming for region resurrection first. This is to solve the
> +% problem with region resurrection. Then that transformed program is
> +% transformed again to solve the problem with if-then-else. Note that the
> +% first transformation may add to the problem with if-then-else, e.g.,
> +% when it introduces reverse renaming to a non-local variable inside the
> +% condition goal of an if-then-else.
> +%
> %-----------------------------------------------------------------------------%
>
> :- module transform_hlds.rbmm.condition_renaming.
> @@ -31,12 +42,14 @@
> :- import_module transform_hlds.rbmm.region_resurrection_renaming.
>
> :- import_module map.
> +:- import_module set.
> +:- import_module string.
>
> %-----------------------------------------------------------------------------%
>
> :- type proc_goal_path_regions_table ==
> 	map(pred_proc_id, goal_path_regions_table).
> -:- type goal_path_regions_table == map(goal_path, region_set).
> +:- type goal_path_regions_table == map(goal_path, set(string)).
>
> 	% This predicate collects two pieces of information.
> 	% 1. The non-local regions of if-then-elses.
> @@ -46,17 +59,18 @@
> 	% 2. The regions which are created (get bound) in the condition
> 	% goals of if-then-else.
> 	% We will only store information about a procedure if the information
> -	% exists. That means, for example, there is no entry from PPId to
> -	% empty.
> +	% exists. That means, for example, there is no entry which maps a PPId
> +	% to empty.
> 	%
> 	% This information is used to compute the regions which need to be
> 	% renamed, i.e., both non-local and created in the condition of an
> 	% if-then-else.
> 	%
> :- pred collect_non_local_and_in_cond_regions(module_info::in,
> -	proc_pp_region_set_table::in, proc_pp_region_set_table::in,
> -	proc_goal_path_regions_table::out, proc_goal_path_regions_table::out)
> -	is det.
> +	rpta_info_table::in, proc_pp_region_set_table::in,
> +	proc_pp_region_set_table::in, renaming_table::in,
> +	renaming_annotation_table::in, proc_goal_path_regions_table::out,
> +	proc_goal_path_regions_table::out) is det.
>
> 	% After having the 2 pieces of information calculated above, this step
> 	% is simple. The only thing to note here is that we will only store
>             module_info_proc_info(ModuleInfo, PPId, ProcInfo0),
> 			fill_goal_path_slots(ModuleInfo, ProcInfo0, ProcInfo),
>             proc_info_get_goal(ProcInfo, Goal),
> +			map.lookup(RptaInfoTable, PPId, rpta_info(Graph, _)),
> 			map.lookup(LRBeforeTable, PPId, LRBeforeProc),
> 			map.lookup(LRAfterTable, PPId, LRAfterProc),
> -            collect_non_local_and_in_cond_regions_goal(LRBeforeProc,
> -				LRAfterProc, Goal,
> +			( if	map.search(ResurRenamingTable, PPId,
> +						ResurRenamingProc0)
> +			  then	ResurRenamingProc = ResurRenamingProc0
> +			  else	ResurRenamingProc = map.init
> +			),
> +			( if	map.search(ResurRenamingAnnoTable, PPId,
> +						ResurRenamingAnnoProc0)
> +			  then	ResurRenamingAnnoProc = ResurRenamingAnnoProc0
> +			  else	ResurRenamingAnnoProc = map.init
> +			),

Fix the indentation of the if-then-elses here ...

> +            collect_non_local_and_in_cond_regions_goal(Graph,
> +				LRBeforeProc, LRAfterProc, ResurRenamingProc,
> +				ResurRenamingAnnoProc, Goal,
> 				map.init, NonLocalRegionsProc,
> 				map.init, InCondRegionsProc),
> 			( if	map.count(NonLocalRegionsProc) = 0
> -			  then	true
> -			  else	svmap.set(PPId, NonLocalRegionsProc, !NonLocalRegionsTable)
> +			  then	true
> +			  else	svmap.set(PPId, NonLocalRegionsProc,
> +						!NonLocalRegionsTable)
> 			),
> 			( if	map.count(InCondRegionsProc) = 0
> -			  then	true
> -			  else	svmap.set(PPId, InCondRegionsProc, !InCondRegionsTable)
> +			  then	true
> +			  else	svmap.set(PPId, InCondRegionsProc,
> +						!InCondRegionsTable)
> 			)

... and here.

>     ).
>
> -:- pred collect_non_local_and_in_cond_regions_goal(pp_region_set_table::in,
> -	pp_region_set_table::in, hlds_goal::in,
> +:- pred collect_non_local_and_in_cond_regions_goal(rpt_graph::in,
> +	pp_region_set_table::in, pp_region_set_table::in,
> +	renaming_proc::in, renaming_annotation_proc::in, hlds_goal::in,
>     goal_path_regions_table::in, goal_path_regions_table::out,
> 	goal_path_regions_table::in, goal_path_regions_table::out) is det.
>
> -collect_non_local_and_in_cond_regions_goal(LRBeforeProc, LRAfterProc, Goal,
> +collect_non_local_and_in_cond_regions_goal(Graph, LRBeforeProc, LRAfterProc,
> +		ResurRenamingProc, ResurRenamingAnnoProc, Goal,
> 		!NonLocalRegionsProc, !InCondRegionsProc) :-
> 	Goal = hlds_goal(Expr, _),
> -	collect_non_local_and_in_cond_regions_expr(LRBeforeProc, LRAfterProc,
> -		Expr, !NonLocalRegionsProc, !InCondRegionsProc).
> +	collect_non_local_and_in_cond_regions_expr(Graph, LRBeforeProc,
> +		LRAfterProc, ResurRenamingProc, ResurRenamingAnnoProc, Expr,
> +		!NonLocalRegionsProc, !InCondRegionsProc).
>
> -:- pred collect_non_local_and_in_cond_regions_expr(pp_region_set_table::in,
> -	pp_region_set_table::in, hlds_goal_expr::in,
> +:- pred collect_non_local_and_in_cond_regions_expr(rpt_graph::in,
> +	pp_region_set_table::in, pp_region_set_table::in,
> +	renaming_proc::in, renaming_annotation_proc::in, hlds_goal_expr::in,
> 	goal_path_regions_table::in, goal_path_regions_table::out,
> 	goal_path_regions_table::in, goal_path_regions_table::out) is det.
>
> -collect_non_local_and_in_cond_regions_expr(LRBeforeProc, LRAfterProc,
> -		conj(_, Conjs), !NonLocalRegionsProc, !InCondRegionsProc) :-
> -    list.foldl2(collect_non_local_and_in_cond_regions_goal(LRBeforeProc,
> -					LRAfterProc),
> +collect_non_local_and_in_cond_regions_expr(Graph, LRBeforeProc, LRAfterProc,
> +		ResurRenamingProc, ResurRenamingAnnoProc, conj(_, Conjs),
> +		!NonLocalRegionsProc, !InCondRegionsProc) :-
> +    list.foldl2(collect_non_local_and_in_cond_regions_goal(Graph,
> +					LRBeforeProc, LRAfterProc,
> +					ResurRenamingProc,
> +					ResurRenamingAnnoProc),
> 		Conjs, !NonLocalRegionsProc, !InCondRegionsProc).
>
> -collect_non_local_and_in_cond_regions_expr(_, _,
> +collect_non_local_and_in_cond_regions_expr(_, _, _, _, _,
> 		plain_call(_, _, _, _, _, _),
> 		!NonLocalRegionsProc, !InCondRegionsProc).
> -collect_non_local_and_in_cond_regions_expr(_, _, generic_call(_, _, _, _),
> +collect_non_local_and_in_cond_regions_expr(_, _, _, _, _,
> +		generic_call(_, _, _, _),
> 		!NonLocalRegionsProc, !InCondRegionsProc).
> -collect_non_local_and_in_cond_regions_expr(_, _,
> +collect_non_local_and_in_cond_regions_expr(_, _, _, _, _,
> 		call_foreign_proc(_, _, _, _, _, _, _),
> 		!NonLocalRegionsProc, !InCondRegionsProc).
>
> -collect_non_local_and_in_cond_regions_expr(LRBeforeProc, LRAfterProc,
> -		switch(_, _, Cases), !NonLocalRegionsProc, !InCondRegionsProc) :-
> -    list.foldl2(collect_non_local_and_in_cond_regions_case(LRBeforeProc,
> -					LRAfterProc),
> +collect_non_local_and_in_cond_regions_expr(Graph, LRBeforeProc, LRAfterProc,
> +		ResurRenamingProc, ResurRenamingAnnoProc, switch(_, _, Cases),
> +		!NonLocalRegionsProc, !InCondRegionsProc) :-
> +    list.foldl2(collect_non_local_and_in_cond_regions_case(Graph,
> +					LRBeforeProc, LRAfterProc,
> +					ResurRenamingProc,
> +					ResurRenamingAnnoProc),
> 		Cases, !NonLocalRegionsProc, !InCondRegionsProc).
> -collect_non_local_and_in_cond_regions_expr(LRBeforeProc, LRAfterProc,
> -		disj(Disjs), !NonLocalRegionsProc, !InCondRegionsProc) :-
> -    list.foldl2(collect_non_local_and_in_cond_regions_goal(LRBeforeProc,
> -					LRAfterProc),
> +collect_non_local_and_in_cond_regions_expr(Graph, LRBeforeProc, LRAfterProc,
> +		ResurRenamingProc, ResurRenamingAnnoProc, disj(Disjs),
> +		!NonLocalRegionsProc, !InCondRegionsProc) :-
> +    list.foldl2(collect_non_local_and_in_cond_regions_goal(Graph,
> +					LRBeforeProc, LRAfterProc,
> +					ResurRenamingProc,
> +					ResurRenamingAnnoProc),
> 		Disjs, !NonLocalRegionsProc, !InCondRegionsProc).
> -collect_non_local_and_in_cond_regions_expr(LRBeforeProc, LRAfterProc,
> -		negation(Goal), !NonLocalRegionsProc, !InCondRegionsProc) :-
> -    collect_non_local_and_in_cond_regions_goal(LRBeforeProc, LRAfterProc,
> -		Goal, !NonLocalRegionsProc, !InCondRegionsProc).
> -collect_non_local_and_in_cond_regions_expr(_, _, unify(_, _, _, _, _),
> -		!NonLocalRegionsProc, !InCondRegionsProc).
> +collect_non_local_and_in_cond_regions_expr(Graph, LRBeforeProc, LRAfterProc,
> +		ResurRenamingProc, ResurRenamingAnnoProc, negation(Goal),
> +		!NonLocalRegionsProc, !InCondRegionsProc) :-
> +    collect_non_local_and_in_cond_regions_goal(Graph, LRBeforeProc,
> +		LRAfterProc, ResurRenamingProc, ResurRenamingAnnoProc, Goal,
> +		!NonLocalRegionsProc, !InCondRegionsProc).
> +collect_non_local_and_in_cond_regions_expr(_, _, _, _, _,
> +		unify(_, _, _, _, _), !NonLocalRegionsProc, !InCondRegionsProc).
>
> -collect_non_local_and_in_cond_regions_expr(LRBeforeProc, LRAfterProc,
> -		scope(_, Goal), !NonLocalRegionsProc, !InCondRegionsProc) :-
> -	collect_non_local_and_in_cond_regions_goal(LRBeforeProc, LRAfterProc,
> -		Goal, !NonLocalRegionsProc, !InCondRegionsProc).
> +collect_non_local_and_in_cond_regions_expr(Graph, LRBeforeProc, LRAfterProc,
> +		ResurRenamingProc, ResurRenamingAnnoProc, scope(_, Goal),
> +		!NonLocalRegionsProc, !InCondRegionsProc) :-
> +	collect_non_local_and_in_cond_regions_goal(Graph, LRBeforeProc,
> +		LRAfterProc, ResurRenamingProc, ResurRenamingAnnoProc, Goal,
> +		!NonLocalRegionsProc, !InCondRegionsProc).
>
> -collect_non_local_and_in_cond_regions_expr(LRBeforeProc, LRAfterProc, Expr,
> +collect_non_local_and_in_cond_regions_expr(Graph, LRBeforeProc, LRAfterProc,
> +		ResurRenamingProc, ResurRenamingAnnoProc, Expr,
> 		!NonLocalRegionProc, !InCondRegionsProc) :-
> 	Expr = if_then_else(_, Cond, Then, Else),
>
> 	% We only care about regions created inside condition goals.
> -	collect_regions_created_in_condition(LRBeforeProc, LRAfterProc, Cond,
> +	collect_regions_created_in_condition(Graph, LRBeforeProc, LRAfterProc,
> +		ResurRenamingProc, ResurRenamingAnnoProc, Cond,
> 		!InCondRegionsProc),
>
> 	% The sets of non_local regions in the (Cond, Then) and in the (Else)
> 	% branch are the same, therefore we will only calculate in one of them.
> 	% As it is here, we calculate for (Else) with the hope that it is
> 	% usually more efficient (only Else compared to both Cond and Then).
> -    collect_non_local_and_in_cond_regions_goal(LRBeforeProc, LRAfterProc,
> +    collect_non_local_and_in_cond_regions_goal(Graph, LRBeforeProc,
> +		LRAfterProc, ResurRenamingProc, ResurRenamingAnnoProc,
> 		Cond, !NonLocalRegionProc, !InCondRegionsProc),
> -    collect_non_local_and_in_cond_regions_goal(LRBeforeProc, LRAfterProc,
> +    collect_non_local_and_in_cond_regions_goal(Graph, LRBeforeProc,
> +		LRAfterProc, ResurRenamingProc, ResurRenamingAnnoProc,
> 		Then, !NonLocalRegionProc, !InCondRegionsProc),
> -    collect_non_local_regions_in_ite(LRBeforeProc, LRAfterProc, Else,
> +    collect_non_local_regions_in_ite(Graph, LRBeforeProc, LRAfterProc,
> +		ResurRenamingProc, ResurRenamingAnnoProc, Else,
> 		!NonLocalRegionProc).
>
> -collect_non_local_and_in_cond_regions_expr(_, _, shorthand(_),
> +collect_non_local_and_in_cond_regions_expr(_, _, _, _, _, shorthand(_),
> 		!NonLocalRegionProc, !InCondRegionsProc) :-
>     unexpected(this_file, "collect_non_local_and_in_cond_regions_expr: "
> 		++ "shorthand not handled").
>
> -:- pred collect_non_local_and_in_cond_regions_case(pp_region_set_table::in,
> -	pp_region_set_table::in, case::in,
> +:- pred collect_non_local_and_in_cond_regions_case(rpt_graph::in,
> +	pp_region_set_table::in, pp_region_set_table::in,
> +	renaming_proc::in, renaming_annotation_proc::in, case::in,
> 	goal_path_regions_table::in, goal_path_regions_table::out,
> 	goal_path_regions_table::in, goal_path_regions_table::out) is det.
>
> -collect_non_local_and_in_cond_regions_case(LRBeforeProc, LRAfterProc, Case,
> +collect_non_local_and_in_cond_regions_case(Graph, LRBeforeProc, LRAfterProc,
> +		ResurRenamingProc, ResurRenamingAnnoProc, Case,
> 		!NonLocalRegionProc, !InCondRegionsProc) :-
>     Case = case(_, Goal),
> -    collect_non_local_and_in_cond_regions_goal(LRBeforeProc, LRAfterProc,
> -		Goal, !NonLocalRegionProc, !InCondRegionsProc).
> -
> -:- pred collect_non_local_regions_in_ite(pp_region_set_table::in,
> -	pp_region_set_table::in, hlds_goal::in, goal_path_regions_table::in,
> -	goal_path_regions_table::out) is det.
> +    collect_non_local_and_in_cond_regions_goal(Graph, LRBeforeProc,
> +		LRAfterProc, ResurRenamingProc, ResurRenamingAnnoProc, Goal,
> +		!NonLocalRegionProc, !InCondRegionsProc).
> +
> +:- pred collect_non_local_regions_in_ite(rpt_graph::in,
> +	pp_region_set_table::in, pp_region_set_table::in, renaming_proc::in,
> +	renaming_annotation_proc::in, hlds_goal::in,
> +	goal_path_regions_table::in, goal_path_regions_table::out) is det.
>
> -collect_non_local_regions_in_ite(LRBeforeProc, LRAfterProc, GoalInIte,
> +collect_non_local_regions_in_ite(Graph, LRBeforeProc, LRAfterProc,
> +		ResurRenamingProc, ResurRenamingAnnoProc, GoalInIte,
> 		!NonLocalRegionProc) :-
> 	GoalInIte = hlds_goal(Expr, Info),
> 	( if	goal_is_atomic(Expr)


...

> @@ -324,17 +450,22 @@
> 		% The current NonLocalRegions are attached to the goal path to
> 		% the corresponding condition.
> 		PathToCond = [step_ite_cond | Steps],
> -		( if	map.search(!.NonLocalRegionProc, PathToCond, NonLocalRegions0)
> +		( if	map.search(!.NonLocalRegionProc, PathToCond,
> +					NonLocalRegions0)
> 		  then
> -				set.union(NonLocalRegions0, Created, NonLocalRegions1),
> -				set.difference(NonLocalRegions1, Removed, NonLocalRegions)
> +				set.union(NonLocalRegions0, Created,
> +					NonLocalRegions1),
> +				set.difference(NonLocalRegions1, Removed,
> +					NonLocalRegions)
> 		  else
> -				set.difference(Created, Removed, NonLocalRegions)
> +				set.difference(Created, Removed,
> +					NonLocalRegions)
> 		),

Fix the indentation above.

...

> Index: rbmm.region_transformation.m
> ===================================================================
> RCS file: rbmm.region_transformation.m
> diff -N rbmm.region_transformation.m
> --- /dev/null	1 Jan 1970 00:00:00 -0000
> +++ rbmm.region_transformation.m	29 Jun 2007 02:22:04 -0000
> @@ -0,0 +1,1008 @@
> +%-----------------------------------------------------------------------------%
> +% vim: ft=mercury ts=4 sw=4
> +%-----------------------------------------------------------------------------%
> +% Copyright (C) 2007 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: rbmm.region_transformation.m
> +% Main author: quan.
> +%
> +% This module annotates the HLDS with region information.
> +% The region information includes:
> +% - Add extra region arguments (to pass regions around) to procedures and
> +% calls.
> +% - Update how_to_construct of construction unifications so that we can
> +% construct terms in a region.
> +% - Add region builtin calls (defined in region_builtin.m).
> +%
> +%-----------------------------------------------------------------------------%

...

> +%-----------------------------------------------------------------------------%
> +
> +	% Represent mapping from region name to a program variable that
> +	% represents the region.
> +	%
> +:- type name_to_prog_var_table == map(pred_proc_id, name_to_prog_var).
> +:- type name_to_prog_var == map(string, prog_var).
> +
> +	% XXX Besides changing the HLDS, this predicate also returns a mapping
> +	% from a region name to a program variable which represents the
> +	% region. We will only create a new program variable for a region
> +	% name which is not yet in the map. Currently this map is only used
> +	% in this transformation. If we do not need the map later on we should
> +	% not return it.
> +	%
> +:- pred region_transform(rpta_info_table::in, proc_region_set_table::in,
> +	proc_region_set_table::in, proc_region_set_table::in,
> +	proc_pp_pair_region_list_table::in,
> +	renaming_table::in, renaming_table::in, annotation_table::in,
> +	renaming_annotation_table::in, renaming_annotation_table::in,
> +	name_to_prog_var_table::in, name_to_prog_var_table::out,
> +	module_info::in, module_info::out) is det.

...

> +region_transform(RptaInfoTable, ConstantRTable, DeadRTable, BornRTable,
> +		ActualRegionArgTable, ResurRenamingTable, IteRenamingTable,
> +		AnnotationTable, ResurRenamingAnnoTable, IteRenamingAnnoTable,
> +		!NameToVarTable, !ModuleInfo) :-
> +	map.foldl2(annotate_pred(DeadRTable, BornRTable), ConstantRTable, [],
> +		PredIds, !ModuleInfo),
> +	list.foldl2(region_transform_pred(RptaInfoTable,
> +		ConstantRTable, DeadRTable, BornRTable, ActualRegionArgTable,
> +		ResurRenamingTable, IteRenamingTable,
> +		AnnotationTable, ResurRenamingAnnoTable, IteRenamingAnnoTable),
> +		PredIds, !NameToVarTable, !ModuleInfo),
> +	% We can only do the followings when all the procedures have been
> +	% annotated with region information and recorded. This is necessary
> +	% because recompute_instmap_delta_proc and repuritycheck_proc need to
> +	% look up information about the (annotated) called procedures.
> +	%
> +    list.foldl(update_instmap_delta_pred, PredIds, !ModuleInfo),
> +	list.foldl(check_purity_pred, PredIds, !ModuleInfo).
> +
> +	% This predicate updates pred_info structure. The following information
> +	% is updated:
> +	% 1. Original arity: orig_arity, which is updated with the old value +
> +	% the number of region arguments.
> +	% 2. Argument types: arg_types, updated with region type for region
> +	% arguments.
> +	%
> +:- pred annotate_pred(proc_region_set_table::in, proc_region_set_table::in,
> +	pred_proc_id::in, region_set::in, list(pred_id)::in, list(pred_id)::out,
> +	module_info::in, module_info::out) is det.
> +
> +annotate_pred(DeadRTable, BornRTable, PPId, ConstantR, !Processed,
> +		!ModuleInfo) :-
> +	PPId = proc(PredId, _),
> +	( if	list.member(PredId, !.Processed)
> +	  then	true
> +	  else
> +			some [!PredInfo] (
> +				module_info_pred_info(!.ModuleInfo, PredId,
> +					!:PredInfo),
> +				map.lookup(DeadRTable, PPId, DeadR),
> +				map.lookup(BornRTable, PPId, BornR),
> +				NumberOfRegArgs = set.count(DeadR) +
> +					set.count(BornR) + set.count(ConstantR),
> +				Arity = pred_info_orig_arity(!.PredInfo),
> +				pred_info_set_orig_arity(
> +					Arity + NumberOfRegArgs, !PredInfo),
> +
> +				list.duplicate(NumberOfRegArgs,
> +					make_region_type, RegionTypes),
> +				pred_info_get_arg_types(!.PredInfo, TypeVarSet,
> +					ExistQuantTVars, ArgTypes0),
> +				PredOrFunc =
> +					pred_info_is_pred_or_func(!.PredInfo),
> +				(
> +					PredOrFunc = pf_predicate,
> +					ArgTypes = ArgTypes0 ++ RegionTypes
> +				;
> +					PredOrFunc = pf_function,
> +					% The output of function is always at
> +					% the last.
> +					list.split_last_det(ArgTypes0,
> +						BeforeLast, Last),
> +					ArgTypes = BeforeLast ++ RegionTypes
> +						++ [Last]
> +				),
> +				pred_info_set_arg_types(TypeVarSet,
> +					ExistQuantTVars, ArgTypes, !PredInfo),
> +				module_info_set_pred_info(PredId, !.PredInfo,
> +					!ModuleInfo)
> +			),
> +			!:Processed = [PredId | !.Processed]
> +	).
> +
> +	% This predicate transforms the procedures of a predicate.
> +	%
> +:- pred region_transform_pred(rpta_info_table::in, proc_region_set_table::in,
> +	proc_region_set_table::in, proc_region_set_table::in,
> +	proc_pp_pair_region_list_table::in,
> +	renaming_table::in, renaming_table::in, annotation_table::in,
> +	renaming_annotation_table::in, renaming_annotation_table::in,
> +	pred_id::in, name_to_prog_var_table::in, name_to_prog_var_table::out,
> +	module_info::in, module_info::out) is det.
> +
> +region_transform_pred(RptaInfoTable, ConstantRTable, DeadRTable, BornRTable,
> +		ActualRegionArgTable, ResurRenamingTable, IteRenamingTable,
> +		AnnotationTable, ResurRenamingAnnoTable, IteRenamingAnnoTable,
> +		PredId, !NameToVarTable, !ModuleInfo) :-
> +    module_info_pred_info(!.ModuleInfo, PredId, PredInfo),
> +    ProcIds = pred_info_non_imported_procids(PredInfo),
> +    list.foldl2(region_transform_proc(RptaInfoTable,
> +		ConstantRTable, DeadRTable, BornRTable, ActualRegionArgTable,
> +		ResurRenamingTable, IteRenamingTable,
> +		AnnotationTable, ResurRenamingAnnoTable, IteRenamingAnnoTable,
> +		PredId), ProcIds, !NameToVarTable, !ModuleInfo).
> +
> +	% This predicate updates the proc_info data structure, representing
> +	% a procedure.
> +	% - Introduce new variables for regions (and their region types).
> +	% - Update headvars with region arguments (types and modes).
> +	% - Update the body
> +	%	+ region instructions,
> +	%	+ actual region arguments at call sites,
> +	%	+ how_to_construct at construction unifications.
> +	% - *Requantify* the annotated proc.
> +	% As said above, we will recompute instmap delta, recheck purity for
> +	% this annotated procedure after all the procedures have been
> +	% transformed.
> +	%
> +:- pred region_transform_proc(rpta_info_table::in, proc_region_set_table::in,
> +	proc_region_set_table::in, proc_region_set_table::in,
> +	proc_pp_pair_region_list_table::in,
> +	renaming_table::in, renaming_table::in, annotation_table::in,
> +	renaming_annotation_table::in, renaming_annotation_table::in,
> +	pred_id::in, proc_id::in, name_to_prog_var_table::in,
> +	name_to_prog_var_table::out, module_info::in, module_info::out) is det.
> +
> +region_transform_proc(RptaInfoTable, ConstantRTable, DeadRTable, BornRTable,
> +		ActualRegionArgTable, ResurRenamingTable, IteRenamingTable,
> +		AnnotationTable, ResurRenamingAnnoTable, IteRenamingAnnoTable,
> +		PredId, ProcId, !NameToVarTable, !ModuleInfo) :-
> +    PPId = proc(PredId, ProcId),
> +	module_info_pred_proc_info(!.ModuleInfo, PPId, PredInfo0, ProcInfo0),
> +	fill_goal_path_slots(!.ModuleInfo, ProcInfo0, ProcInfo1),
> +	proc_info_get_varset(ProcInfo1, VarSet0),
> +	proc_info_get_vartypes(ProcInfo1, VarTypes0),
> +	proc_info_get_headvars(ProcInfo1, HeadVars0),
> +	proc_info_get_argmodes(ProcInfo1, ActualArgModes0),
> +	proc_info_get_goal(ProcInfo1, Goal0),
> +	map.lookup(RptaInfoTable, PPId, rpta_info(Graph, _)),
> +	map.lookup(ConstantRTable, PPId, ConstantR),
> +	map.lookup(DeadRTable, PPId, DeadR),
> +	map.lookup(BornRTable, PPId, BornR),
> +	map.lookup(ActualRegionArgTable, PPId, ActualRegionArgProc),
> +	( if	map.search(ResurRenamingTable, PPId, ResurRenamingProc0)
> +	  then
> +			ResurRenamingProc = ResurRenamingProc0,
> +			map.lookup(ResurRenamingAnnoTable, PPId,
> +				ResurRenamingAnnoProc)
> +	  else
> +			ResurRenamingProc = map.init,
> +			ResurRenamingAnnoProc = map.init
> +	),
> +	( if	map.search(IteRenamingTable, PPId, IteRenamingProc0)
> +	  then
> +			IteRenamingProc = IteRenamingProc0,
> +			map.lookup(IteRenamingAnnoTable, PPId,
> +				IteRenamingAnnoProc)
> +	  else
> +			IteRenamingProc = map.init,
> +			IteRenamingAnnoProc = map.init
> +	),
> +	map.lookup(AnnotationTable, PPId, AnnotationProc),
> +	NameToVar0 = map.init,
> +	annotate_proc(!.ModuleInfo, PredInfo0, Graph, ConstantR, DeadR, BornR,
> +		ActualRegionArgProc, ResurRenamingProc, IteRenamingProc,
> +		AnnotationProc, ResurRenamingAnnoProc, IteRenamingAnnoProc,
> +		VarSet0, _, VarTypes0, _, HeadVars0, _, ActualArgModes0, _,
> +		Goal0, _, NameToVar0, NameToVar, ProcInfo1, ProcInfo2),
> +	requantify_proc(ProcInfo2, ProcInfo),
> +	module_info_set_pred_proc_info(PPId, PredInfo0, ProcInfo, !ModuleInfo),
> +	svmap.det_insert(PPId, NameToVar, !NameToVarTable).
> +
> +	% Currently for a procedure we annotate the following information:
> +	% 1. VarSet with region variables
> +	% 2. VarTypes with region variables and their types
> +	% 3. HeadVars with formal region arguments
> +	% 4. ActualHeadModes with the modes for region variables
> +	% 5. Body:
> +	%	+ new region arguments at calls
> +	%	+ new calls to region instructions
> +	%
> +:- pred annotate_proc(module_info::in, pred_info::in, rpt_graph::in,
> +	region_set::in, region_set::in, region_set::in,
> +	pp_pair_region_list_table::in, renaming_proc::in, renaming_proc::in,
> +	annotation_proc::in, renaming_annotation_proc::in,
> +	renaming_annotation_proc::in, prog_varset::in, prog_varset::out,
> +	vartypes::in, vartypes::out, list(prog_var)::in, list(prog_var)::out,
> +	list(mer_mode)::in, list(mer_mode)::out, hlds_goal::in, hlds_goal::out,
> +	name_to_prog_var::in, name_to_prog_var::out, proc_info::in,
> +	proc_info::out) is det.
> +
> +annotate_proc(ModuleInfo, PredInfo, Graph, ConstantR, DeadR, BornR,
> +		ActualRegionArgProc, ResurRenamingProc, IteRenamingProc,
> +		AnnotationProc, ResurRenamingAnnoProc, IteRenamingAnnoProc,
> +		!VarSet, !VarTypes, !HeadVars, !ActualArgModes, !Goal,
> +		!NameToVar, !ProcInfo) :-
> +	region_transform_goal(ModuleInfo, Graph, ResurRenamingProc,
> +		IteRenamingProc, ActualRegionArgProc,
> +		AnnotationProc, ResurRenamingAnnoProc, IteRenamingAnnoProc,
> +		!Goal, !NameToVar, !VarSet, !VarTypes),
> +
> +	% Computing head_vars.

That's a bit vague.  I suggest something like:

 	Add extra variables to the head of the procedure that
 	correspond to the introduced region arguments.

Document the convention that you are using when introducing these new
arguments.

e.g. for predicates:

 	<OrigArgs> ==> <OrigArgs> <InputRegionArgs> <OutputRegionArgs>

for functions:

 	<OrigArgs> <RetVal> ==>
 		<OrigArgs> <InputRegionArgs> <OutputRegionArgs> <RetVal>


> +	% Note that formal region arguments are not subjected to renaming.
> +	set.to_sorted_list(ConstantR, LConstantR),
> +	set.to_sorted_list(DeadR, LDeadR),
> +	set.to_sorted_list(BornR, LBornR),
> +	FormalInputNodes = LConstantR ++ LDeadR,
> +	FormalNodes = FormalInputNodes ++ LBornR,
> +	list.map_foldl3(node_to_var(Graph), FormalNodes, FormalRegionArgs,
> +		!NameToVar, !VarSet, !VarTypes),
> +
> +	% Computing actual_head_modes.
> +	InMode = in_mode,
> +	OutMode = out_mode,
> +	list.duplicate(list.length(FormalInputNodes), InMode, InModes),
> +	list.duplicate(list.length(LBornR), OutMode, OutModes),
> +
> +	% One thing to notice here is that the output of a function needs
> +	% to be the last argument.
> +	PredOrFunc = pred_info_is_pred_or_func(PredInfo),
> +	(
> +		PredOrFunc = pf_predicate,
> +		!:HeadVars = !.HeadVars ++ FormalRegionArgs,
> +		!:ActualArgModes = !.ActualArgModes ++ InModes ++ OutModes
> +	;
> +		PredOrFunc = pf_function,
> +		list.split_last_det(!.HeadVars, BeforeLastHeadVar, LastHeadVar),
> +		!:HeadVars = BeforeLastHeadVar ++ FormalRegionArgs
> +			++ [LastHeadVar],
> +		list.split_last_det(!.ActualArgModes, BeforeLastHeadMode,
> +			LastHeadMode),
> +		!:ActualArgModes = BeforeLastHeadMode ++ InModes
> +			++ OutModes ++ [LastHeadMode]
> +	),
> +
> +	proc_info_set_varset(!.VarSet, !ProcInfo),
> +	proc_info_set_goal(!.Goal, !ProcInfo),
> +	proc_info_set_vartypes(!.VarTypes, !ProcInfo),
> +	proc_info_set_headvars(!.HeadVars, !ProcInfo),
> +	proc_info_set_argmodes(!.ActualArgModes, !ProcInfo).
> +
> +	% Basically, we will turn this atomic goal and all the region
> +	% annotations attached to (before and after) it into a
> +	% conjunction. When there is no annotation, the goal is just
> +	% transformed and returned.
> +	% If the newly created conjunction is a conjunct of a compounding
> +	% conjunction then it will be flattened.
> +	%
> +	% Note: When both renamings (for resurrection and if-then-else) of a
> +	% region exist at a program point, we will apply the resurrection one.
> +	% This is due to the fact that when reasonning about what renaming is
> +	% needed for if-then-else we have taken into account the changes
> +	% caused by renaming and annotations needed for resurrection problem.
> +	%
> +:- pred region_transform_goal(module_info::in, rpt_graph::in,
> +	renaming_proc::in, renaming_proc::in, pp_pair_region_list_table::in,
> +	annotation_proc::in, renaming_annotation_proc::in,
> +	renaming_annotation_proc::in, hlds_goal::in, hlds_goal::out,
> +	name_to_prog_var::in, name_to_prog_var::out,
> +	prog_varset::in, prog_varset::out, vartypes::in, vartypes::out) is det.
> +
> +region_transform_goal(ModuleInfo, Graph, ResurRenamingProc, IteRenamingProc,
> +		ActualRegionArgProc, AnnotationProc, ResurRenamingAnnoProc,
> +		IteRenamingAnnoProc, !Goal, !NameToVar, !VarSet, !VarTypes) :-
> +    !.Goal = hlds_goal(GoalExpr0, Info0),
> +	(	goal_is_atomic(GoalExpr0)
> +	->
> +		ProgPoint = program_point_init(Info0),
> +		ProgPoint = pp(Context, _),
> +		find_renamings_at_prog_point(ResurRenamingProc, IteRenamingProc,
> +			ProgPoint, ResurRenaming, IteRenaming),
> +
> +		% Depending on the expression, this call will annotate
> +		% - a call with actual region arguments,
> +		% - a construction unification with a region to construct in.
> +		region_transform_goal_expr(ModuleInfo, Graph, ResurRenaming,
> +			IteRenaming, ActualRegionArgProc, ProgPoint,
> +			GoalExpr0, GoalExpr, Info0, Info, !NameToVar, !VarSet,
> +			!VarTypes),
> +
> +		% Assignment unifications due to ite renaming.
> +		assignments_from_ite_renaming_anno(IteRenamingAnnoProc,
> +			ProgPoint, !NameToVar, !VarSet, !VarTypes,
> +			[], IteRenamingAssignments),
> +
> +		% Region instructions before and after this program point.
> +		(	map.search(AnnotationProc, ProgPoint,
> +				before_after(Before, After))
> +		->
> +			% Region instructions before this program point.
> +			list.foldl4(region_instruction_to_conj(ModuleInfo,
> +				Context, ResurRenaming, IteRenaming), Before,
> +				!NameToVar, !VarSet, !VarTypes,
> +				IteRenamingAssignments, Conjs1),
> +
> +			% The goal at this program point itself.
> +			Conjs2 = Conjs1 ++ [hlds_goal(GoalExpr, Info)],
> +
> +			% Region instructions after this program point.
> +			list.foldl4(region_instruction_to_conj(ModuleInfo,
> +				Context, ResurRenaming, IteRenaming), After,
> +				!NameToVar, !VarSet, !VarTypes,
> +				Conjs2, Conjs3)
> +		;
> +			% The goal at this program point itself.
> +			Conjs3 = IteRenamingAssignments ++
> +				[hlds_goal(GoalExpr, Info)]
> +		),
> +
> +		% Assignment unifications due to region resurrection renaming.
> +		assignments_from_resur_renaming_anno(ResurRenamingAnnoProc,
> +			ProgPoint, IteRenaming, !NameToVar, !VarSet, !VarTypes,
> +			Conjs3, Conjs),
> +
> +		( if	Conjs = [_, _ | _]
> +		  then
> +				!:Goal = hlds_goal(conj(plain_conj, Conjs),
> +					Info)
> +		  else	!:Goal = hlds_goal(GoalExpr, Info)
> +		)
> +	;
> +		region_transform_compound_goal(ModuleInfo, Graph,
> +			ResurRenamingProc, IteRenamingProc, ActualRegionArgProc,
> +			AnnotationProc, ResurRenamingAnnoProc,
> +			IteRenamingAnnoProc, !Goal, !NameToVar, !VarSet,
> +			!VarTypes)
> +	).
> +
> +:- pred region_transform_goal_expr(module_info::in, rpt_graph::in,
> +	renaming::in, renaming::in, pp_pair_region_list_table::in,
> +	program_point::in, hlds_goal_expr::in, hlds_goal_expr::out,
> +	hlds_goal_info::in, hlds_goal_info::out, name_to_prog_var::in,
> +	name_to_prog_var::out, prog_varset::in, prog_varset::out,
> +	vartypes::in, vartypes::out) is det.
> +
> +	% Annotate procedure calls with actual region arguments.
> +	%
> +region_transform_goal_expr(_, Graph, ResurRenaming, IteRenaming,
> +		ActualRegionArgProc, ProgPoint, !GoalExpr, !GoalInfo,
> +		!NameToVar, !VarSet, !VarTypes) :-
> +	!.GoalExpr = plain_call(CalleePredId, CalleeProcId, Args0, Builtin,
> +		Context, Name),
> +	% XXX Callee may be a builtin or an imported procedure that we have
> +	% not analysed, we just ignore such a call for now.
> +	( if	map.search(ActualRegionArgProc, ProgPoint, ActualNodes0)
> +	  then	ActualNodes = ActualNodes0
> +	  else	ActualNodes = pair([],[])
> +	),
> +	ActualNodes = Ins - Outs,
> +	AllNodes = Ins ++ Outs,
> +	list.map_foldl3(node_to_var_with_both_renamings(Graph,
> +		ResurRenaming, IteRenaming),
> +		AllNodes, ActualRegionArgs, !NameToVar, !VarSet, !VarTypes),
> +	Args = Args0 ++ ActualRegionArgs,
> +	!:GoalExpr = plain_call(CalleePredId, CalleeProcId, Args, Builtin,
> +		Context, Name).
> +
> +	% Annotate construction unifications with regions to construct in.
> +	%
> +region_transform_goal_expr(ModuleInfo, Graph, ResurRenaming, IteRenaming,
> +		_, _, !GoalExpr, !GoalInfo, !NameToVar, !VarSet, !VarTypes) :-
> +	!.GoalExpr = unify(LHS, RHS, Mode, Unification0, Context),
> +    annotate_constructions_unification(ModuleInfo, Graph, ResurRenaming,
> +		IteRenaming, Unification0, Unification, !NameToVar, !VarSet,
> +		!VarTypes),
> +	!:GoalExpr = unify(LHS, RHS, Mode, Unification, Context).
> +
> +region_transform_goal_expr(_, _, _, _, _, _, !GoalExpr, !GoalInfo, !NameToVar,
> +		!VarSet, !VarTypes) :-
> +	!.GoalExpr = generic_call(_, _, _, _),
> +	sorry(this_file,
> +		"region_transform_goal_expr: generic call is not handled.").
> +
> +region_transform_goal_expr(_, _, _, _, _, _, !GoalExpr, !GoalInfo, !NameToVar,
> +		!VarSet, !VarTypes) :-
> +	!.GoalExpr = call_foreign_proc(_, _, _, _, _, _, _),
> +	sorry(this_file, "region_transform_goal_expr: " ++
> +		"call to foreign procedure is not handled").
> +
> +region_transform_goal_expr(_, _, _, _, _, _, !GoalExpr, !GoalInfo, !NameToVar,
> +		!VarSet, !VarTypes) :-
> +	( !.GoalExpr = conj(_, [])
> +	; !.GoalExpr = disj([])
> +	).
> +
> +region_transform_goal_expr(_, _, _, _, _, _, !GoalExpr, !GoalInfo, !NameToVar,
> +		!VarSet, !VarTypes) :-
> +	( !.GoalExpr = conj(_, [_ | _])
> +	; !.GoalExpr = disj([_ | _])
> +	; !.GoalExpr = if_then_else(_, _, _, _)
> +	; !.GoalExpr = negation(_)
> +	; !.GoalExpr = switch(_, _, _)
> +	; !.GoalExpr = scope(_, _)
> +	; !.GoalExpr = shorthand(_)
> +	),
> +	unexpected(this_file,
> +		"region_transform_goal_expr: encounter compound goal").
> +
> +	% Because an atomic goal is turned into a conjunction, we need to
> +	% flatten its compounding conjunction if it is in one.
> +:- pred region_transform_compound_goal(module_info::in, rpt_graph::in,
> +	renaming_proc::in, renaming_proc::in, pp_pair_region_list_table::in,
> +	annotation_proc::in, renaming_annotation_proc::in,
> +	renaming_annotation_proc::in, hlds_goal::in, hlds_goal::out,
> +	name_to_prog_var::in, name_to_prog_var::out,
> +	prog_varset::in, prog_varset::out, vartypes::in, vartypes::out) is det.
> +
> +region_transform_compound_goal(ModuleInfo, Graph,
> +		ResurRenamingProc, IteRenamingProc, ActualRegionArgProc,
> +		AnnotationProc, ResurRenamingAnnoProc, IteRenamingAnnoProc,
> +		hlds_goal(!.GoalExpr, !.GoalInfo), hlds_goal(!:GoalExpr, !:GoalInfo),
> +		!NameToVar, !VarSet, !VarTypes) :-
> +	(
> +		!.GoalExpr = conj(ConjType, [Conj0 | Conjs0]),
> +		list.map_foldl3(region_transform_goal(ModuleInfo, Graph,
> +			ResurRenamingProc, IteRenamingProc,
> +			ActualRegionArgProc, AnnotationProc,
> +			ResurRenamingAnnoProc, IteRenamingAnnoProc),
> +			[Conj0 | Conjs0], Conjs1, !NameToVar, !VarSet,
> +			!VarTypes),
> +		flatten_conj(Conjs1, Conjs),
> +		!:GoalExpr = conj(ConjType, Conjs)
> +	;
> +		!.GoalExpr = disj([Disj0 | Disjs0]),
> +		list.map_foldl3(region_transform_goal(ModuleInfo, Graph,
> +			ResurRenamingProc, IteRenamingProc,
> +			ActualRegionArgProc, AnnotationProc,
> +			ResurRenamingAnnoProc, IteRenamingAnnoProc),
> +			[Disj0 | Disjs0], Disjs, !NameToVar, !VarSet,
> +			!VarTypes),
> +		!:GoalExpr = disj(Disjs)
> +	;
> +		!.GoalExpr = switch(Var, CanFail, Cases0),
> +		list.map_foldl3(region_transform_case(ModuleInfo, Graph,
> +			ResurRenamingProc, IteRenamingProc,
> +			ActualRegionArgProc, AnnotationProc,
> +			ResurRenamingAnnoProc, IteRenamingAnnoProc,
> +			hlds_goal(!.GoalExpr, !.GoalInfo)),
> +			Cases0, Cases, !NameToVar, !VarSet, !VarTypes),
> +		!:GoalExpr = switch(Var, CanFail, Cases)
> +	;
> +		!.GoalExpr = negation(Goal0),
> +		region_transform_goal(ModuleInfo, Graph, ResurRenamingProc,
> +			IteRenamingProc, ActualRegionArgProc, AnnotationProc,
> +			ResurRenamingAnnoProc, IteRenamingAnnoProc, Goal0, Goal,
> +			!NameToVar, !VarSet, !VarTypes),
> +		!:GoalExpr = negation(Goal)
> +	;
> +		!.GoalExpr = scope(Reason, Goal0),
> +		region_transform_goal(ModuleInfo, Graph, ResurRenamingProc,
> +			IteRenamingProc, ActualRegionArgProc, AnnotationProc,
> +			ResurRenamingAnnoProc, IteRenamingAnnoProc, Goal0, Goal,
> +			!NameToVar, !VarSet, !VarTypes),
> +		!:GoalExpr = scope(Reason, Goal)
> +	;
> +		!.GoalExpr = if_then_else(Vars, Cond0, Then0, Else0),
> +		region_transform_goal(ModuleInfo, Graph, ResurRenamingProc,
> +			IteRenamingProc, ActualRegionArgProc, AnnotationProc,
> +			ResurRenamingAnnoProc, IteRenamingAnnoProc, Cond0, Cond,
> +			!NameToVar, !VarSet, !VarTypes),
> +		region_transform_goal(ModuleInfo, Graph, ResurRenamingProc,
> +			IteRenamingProc, ActualRegionArgProc, AnnotationProc,
> +			ResurRenamingAnnoProc, IteRenamingAnnoProc, Then0, Then,
> +			!NameToVar, !VarSet, !VarTypes),
> +		region_transform_goal(ModuleInfo, Graph, ResurRenamingProc,
> +			IteRenamingProc, ActualRegionArgProc, AnnotationProc,
> +			ResurRenamingAnnoProc, IteRenamingAnnoProc, Else0, Else,
> +			!NameToVar, !VarSet, !VarTypes),
> +		!:GoalExpr = if_then_else(Vars, Cond, Then, Else)
> +	;
> +		( !.GoalExpr = shorthand(_)
> +		; !.GoalExpr = unify(_, _, _, _, _)
> +		; !.GoalExpr = plain_call(_, _, _, _, _, _)
> +		; !.GoalExpr = generic_call(_, _, _, _)
> +		; !.GoalExpr = call_foreign_proc(_, _, _, _, _, _, _)
> +		; !.GoalExpr = conj(_, [])
> +		; !.GoalExpr = disj([])
> +		),
> +		unexpected(this_file, "region_transform_compound_goal: " ++
> +			"encounter shorthand or atomic goal")
> +	).
> +
> +	% This predicate needs to be consistent with what are done in
> +	% unify_gen.m, i.e., we will change how_to_construct to
> +	% construct_in_region(RegVar) only when the term is actually
> +	% stored in the heap.
> +	% The current implementation may not be correct.
> +	%
> +:- pred annotate_constructions_unification(module_info::in, rpt_graph::in,
> +	renaming::in, renaming::in, unification::in, unification::out,
> +	name_to_prog_var::in, name_to_prog_var::out,
> +	prog_varset::in, prog_varset::out, vartypes::in, vartypes::out) is det.
> +
> +annotate_constructions_unification(ModuleInfo, Graph, ResurRenaming,
> +		IteRenaming, !Unification, !NameToVar, !VarSet, !VarTypes) :-
> +	!.Unification = construct(Var, ConsId, Args, ArgModes, _HowToConstruct0,
> +		IsUnique, SubInfo),
> +	get_node_by_variable(Graph, Var, Node),
> +	NodeType = rptg_lookup_node_type(Graph, Node),
> +	( if	( type_is_atomic(ModuleInfo, NodeType)
> +			; is_dummy_argument_type(ModuleInfo, NodeType)
> +			)

Fix the indentation there.

> +	  then  true
> +	  else
> +		Name = rptg_lookup_region_name(Graph, Node),
> +		region_name_to_var_with_both_renamings(Name, ResurRenaming,
> +			IteRenaming, RegVar, !NameToVar, !VarSet, !VarTypes),
> +		HowToConstruct = construct_in_region(RegVar),
> +		!:Unification = construct(Var, ConsId, Args, ArgModes,
> +			HowToConstruct, IsUnique, SubInfo)
> +	).
> +
> +annotate_constructions_unification(_, _, _, _, !Unification, !VarSet,
> +		!VarTypes, !NameToVar) :-
> +	(
> +		( !.Unification = deconstruct(_, _, _, _, _, _)
> +		; !.Unification = assign(_, _)
> +		; !.Unification = simple_test(_, _)
> +		)
> +	;
> +		!.Unification = complicated_unify(_, _, _),
> +		unexpected(this_file, "annotate_construction_unification: "
> +			++ "encounter complicated unify")
> +	).
> +
> +	% The process here is related to the way we treat the unifications
> +	% between the switch vars and a constant or a functor of arity zero.
> +	% For more information about the treatment, see rbmm.execution_path.m.
> +	% These unifications are not explicitly present in the goal but we
> +	% still need to insert annotations derived for them into the goal.
> +	% Therefore we will make a conjunction of the annotations attached to an
> +	% implicit unification. We transform the goal separately. Then we make
> +	% another conjunction of the conjunction and the transformed goal.
> +	% Finally, we try to flatten this new conjunction.
> +	%
> +:- pred region_transform_case(module_info::in, rpt_graph::in,
> +	renaming_proc::in, renaming_proc::in, pp_pair_region_list_table::in,
> +	annotation_proc::in, renaming_annotation_proc::in,
> +	renaming_annotation_proc::in, hlds_goal::in, case::in, case::out,
> +	name_to_prog_var::in, name_to_prog_var::out,
> +	prog_varset::in, prog_varset::out, vartypes::in, vartypes::out) is det.
> +
> +region_transform_case(ModuleInfo, Graph, ResurRenamingProc,
> +		IteRenamingProc, ActualRegionArgProc, AnnotationProc,
> +		ResurRenamingAnnoProc, IteRenamingAnnoProc, Switch,
> +		case(ConsId, !.Goal), case(ConsId, !:Goal),
> +		!NameToVar, !VarSet, !VarTypes) :-
> +	(	( ConsId = cons(_, 0)
> +		; ConsId = int_const(_)
> +		; ConsId = string_const(_)
> +		; ConsId = float_const(_)
> +		),
> +		Switch = hlds_goal(switch(_, _, _), Info)
> +	->
> +		ProgPoint = program_point_init(Info),
> +		ProgPoint = pp(Context, _),
> +		find_renamings_at_prog_point(ResurRenamingProc, IteRenamingProc,
> +			ProgPoint, ResurRenaming, IteRenaming),
> +
> +		% Assignment unifications due to ite renaming.
> +		assignments_from_ite_renaming_anno(IteRenamingAnnoProc,
> +			ProgPoint, !NameToVar, !VarSet, !VarTypes,
> +			[], IteRenamingAssignments),
> +
> +		% Region instructions before and after this program
> +		% point.
> +		(	map.search(AnnotationProc, ProgPoint,
> +				before_after(Before, After))
> +		->
> +			% Region instructions before this program point.
> +			list.foldl4(region_instruction_to_conj(
> +				ModuleInfo, Context, ResurRenaming,
> +				IteRenaming), Before, !NameToVar,
> +				!VarSet, !VarTypes,
> +				IteRenamingAssignments, Conjs1),
> +
> +			% Region instructions after this program point.
> +			list.foldl4(region_instruction_to_conj(
> +				ModuleInfo, Context, ResurRenaming,
> +				IteRenaming), After, !NameToVar,
> +				!VarSet, !VarTypes, Conjs1, Conjs2)
> +		;
> +			Conjs2 = IteRenamingAssignments
> +		),
> +
> +		% Assignment unifications due to region resurrection
> +		% renaming.
> +		assignments_from_resur_renaming_anno(ResurRenamingAnnoProc,
> +			ProgPoint, IteRenaming, !NameToVar, !VarSet, !VarTypes,
> +			Conjs2, Conjs),
> +
> +		RemovedGoal = hlds_goal(conj(plain_conj, Conjs), Info)
> +	;
> +		Switch = hlds_goal(_, Info),
> +		RemovedGoal = hlds_goal(conj(plain_conj, []), Info)
> +	),
> +	region_transform_goal(ModuleInfo, Graph, ResurRenamingProc,
> +		IteRenamingProc, ActualRegionArgProc, AnnotationProc,
> +		ResurRenamingAnnoProc, IteRenamingAnnoProc, !Goal, !NameToVar,
> +		!VarSet, !VarTypes),
> +	flatten_conj([RemovedGoal, !.Goal], FlatConjs),
> +	Switch = hlds_goal(_, ConjsInfo),
> +	!:Goal = hlds_goal(conj(plain_conj, FlatConjs), ConjsInfo).
> +
> +:- pred find_renamings_at_prog_point(renaming_proc::in, renaming_proc::in,
> +	program_point::in, renaming::out, renaming::out) is det.
> +
> +find_renamings_at_prog_point(ResurRenamingProc, IteRenamingProc, ProgPoint,
> +		ResurRenaming, IteRenaming) :-
> +	( if	map.search(ResurRenamingProc, ProgPoint, ResurRenaming0)
> +	  then	ResurRenaming = ResurRenaming0
> +	  else	ResurRenaming = map.init
> +	),
> +	( if	map.search(IteRenamingProc, ProgPoint, IteRenaming0)
> +	  then	IteRenaming = IteRenaming0
> +	  else	IteRenaming = map.init
> +	).
> +
> +:- pred assignments_from_ite_renaming_anno(renaming_annotation_proc::in,
> +	program_point::in, name_to_prog_var::in, name_to_prog_var::out,
> +	prog_varset::in, prog_varset::out, vartypes::in, vartypes::out,
> +	hlds_goals::in, hlds_goals::out) is det.
> +
> +assignments_from_ite_renaming_anno(IteRenamingAnnoProc, ProgPoint,
> +		!NameToVar, !VarSet, !VarTypes, !IteRenamingAssignments) :-
> +	% Assignment unifications due to ite renaming.
> +	(	map.search(IteRenamingAnnoProc, ProgPoint, IteRenamingAnnos)
> +	->
> +		list.foldl4(ite_renaming_annotation_to_assignment,
> +			IteRenamingAnnos, !NameToVar, !VarSet, !VarTypes,
> +			!IteRenamingAssignments)
> +	;	true
> +	).
> +
> +:- pred assignments_from_resur_renaming_anno(renaming_annotation_proc::in,
> +	program_point::in, renaming::in, name_to_prog_var::in,
> +	name_to_prog_var::out, prog_varset::in, prog_varset::out,
> +	vartypes::in, vartypes::out, hlds_goals::in, hlds_goals::out) is det.
> +
> +assignments_from_resur_renaming_anno(ResurRenamingAnnoProc, ProgPoint,
> +		IteRenaming, !NameToVar, !VarSet, !VarTypes, !Conjs) :-
> +	(	map.search(ResurRenamingAnnoProc, ProgPoint,
> +			ResurRenamingAnnos)
> +	->
> +		list.foldl4(resur_renaming_annotation_to_assignment(
> +			IteRenaming), ResurRenamingAnnos, !NameToVar, !VarSet,
> +			!VarTypes, !Conjs)
> +	;	true
> +	).
> +
> +	% Return the program variable representing the region which is
> +	% represented by the node in the points-to graph.
> +	% Come up with a new program variable if none exists yet.
> +	% Each node is associated with a region name, so this predicate just
> +	% delegates the task for region_name_to_var.
> +	%
> +:- pred node_to_var(rpt_graph::in, rptg_node::in,
> +	prog_var::out, name_to_prog_var::in, name_to_prog_var::out,
> +	prog_varset::in, prog_varset::out, vartypes::in, vartypes::out) is det.
> +
> +node_to_var(Graph, Node, RegVar, !NameToVar, !VarSet,
> +		!VarTypes) :-
> +	RegName = rptg_lookup_region_name(Graph, Node),
> +	region_name_to_var(RegName, RegVar, !NameToVar, !VarSet, !VarTypes).
> +
> +	% Return the program variable representing the region name.
> +	% Come up with a new one if none exists.
> +	%
> +:- pred region_name_to_var(string::in, prog_var::out,
> +	name_to_prog_var::in, name_to_prog_var::out,
> +	prog_varset::in, prog_varset::out, vartypes::in, vartypes::out) is det.
> +
> +region_name_to_var(Name, RegVar, !NameToVar, !VarSet, !VarTypes) :-
> +	( if	map.search(!.NameToVar, Name, RegVar0)
> +	  then	RegVar = RegVar0
> +	  else
> +			svvarset.new_named_var(Name, RegVar, !VarSet),
> +			svmap.det_insert(RegVar, make_region_type, !VarTypes),
> +			svmap.det_insert(Name, RegVar, !NameToVar)

Fix the indentation there.

> +	).
> +
> +	% The same as node_to_var, but the corresponding region name is
> +	% subjected to resurrection and if-then-else renaming beforehand.
> +	%
> +:- pred node_to_var_with_both_renamings(rpt_graph::in, renaming::in,
> +	renaming::in, rptg_node::in, prog_var::out,
> +	name_to_prog_var::in, name_to_prog_var::out,
> +	prog_varset::in, prog_varset::out, vartypes::in, vartypes::out) is det.
> +
> +node_to_var_with_both_renamings(Graph, ResurRenaming, IteRenaming,
> +		Node, RegVar, !NameToVar, !VarSet, !VarTypes) :-
> +	RegName = rptg_lookup_region_name(Graph, Node),
> +	region_name_to_var_with_both_renamings(RegName, ResurRenaming,
> +		IteRenaming, RegVar, !NameToVar, !VarSet, !VarTypes).
> +
> +	% Resurrection renaming will be applied first. If a renaming exists
> +	% for the name (i.e., the name will be changed to another name) then
> +	% ite renaming need not to be applied because actually it is not
> +	% applicable anymore.
> +	%
> +:- pred region_name_to_var_with_both_renamings(string::in, renaming::in,
> +	renaming::in, prog_var::out,
> +	name_to_prog_var::in, name_to_prog_var::out,
> +	prog_varset::in, prog_varset::out, vartypes::in, vartypes::out) is det.
> +
> +region_name_to_var_with_both_renamings(Name0, ResurRenaming, IteRenaming,
> +		RegVar, !NameToVar, !VarSet, !VarTypes) :-
> +	( if	map.search(ResurRenaming, Name0, Name1)
> +	  then	Name = Name1
> +	  else
> +			( if	map.search(IteRenaming, Name0, Name2)
> +			  then	Name = Name2
> +			  else  Name = Name0
> +			)
> +	),
> +	region_name_to_var(Name, RegVar, !NameToVar, !VarSet, !VarTypes).
> +
> +	% The same as region_name_to_var, but the region name here is
> +	% subjected to resurrection renaming in advance.
> +	%
> +:- pred region_name_to_var_with_renaming(string::in, renaming::in,
> +	prog_var::out, name_to_prog_var::in, name_to_prog_var::out,
> +	prog_varset::in, prog_varset::out, vartypes::in, vartypes::out) is det.
> +
> +region_name_to_var_with_renaming(Name0, ResurRenaming, RegVar,
> +		!NameToVar, !VarSet, !VarTypes) :-
> +	( if	map.search(ResurRenaming, Name0, Name1)
> +	  then	Name = Name1
> +	  else	Name = Name0
> +	),
> +	region_name_to_var(Name, RegVar, !NameToVar, !VarSet, !VarTypes).
> +
> +:- func make_region_type = mer_type.
> +
> +make_region_type = RegionType :-
> +	RegionTypeName = qualified(mercury_region_builtin_module, "region"),
> +	RegionType = defined_type(RegionTypeName, [], kind_star).
> +
> +	% Instruction is of the form: "Tx: xxxxxx R..."
> +	% The first x is the number of the rule, which is not important here.
> +	% The next 6 x is either "remove" or "create", the last part is the
> +	% region name. This region name will be subjected to renaming due to
> +	% if-then-else and region resurrection.
> +	% This predicate turns such an instruction into a call to a suitable
> +	% region builtin.
> +	% XXX  This is temporary. Using string to represent region instructions
> +	% (create, remove, renaming, maybe some more in the future) is not good.
> +	% Region instruction should become a specific type with distinct
> +	% constructor for each kind of instruction.
> +	% XXX  Call to generate_simple_call here seems overkilled because we
> +	% will recompute nonlocals, instmap delta anyway.
> +	%
> +:- pred region_instruction_to_conj(module_info::in, term.context::in,
> +	renaming::in, renaming::in, string::in,
> +	name_to_prog_var::in, name_to_prog_var::out,
> +	prog_varset::in, prog_varset::out, vartypes::in, vartypes::out,
> +	hlds_goals::in, hlds_goals::out) is det.
> +
> +region_instruction_to_conj(ModuleInfo, Context, ResurRenaming, IteRenaming,
> +		Instruction, !NameToVar, !VarSet, !VarTypes, Conjs0, Conjs) :-
> +	string.substring(Instruction, 4, 6, Kind),
> +	string.substring(Instruction, 11, string.length(Instruction) - 11,
> +		RegionName),
> +	region_name_to_var_with_both_renamings(RegionName, ResurRenaming,
> +		IteRenaming, RegVar, !NameToVar, !VarSet, !VarTypes),
> +	(	Kind = "create" ->
> +		generate_simple_call(mercury_region_builtin_module,
> +			"create_region", pf_predicate, only_mode, detism_det,
> +			purity_impure, [RegVar], [], [],
> +			ModuleInfo, Context, CallGoal)
> +	;
> +		Kind = "remove"
> +	->
> +		generate_simple_call(mercury_region_builtin_module,
> +			"remove_region", pf_predicate, only_mode, detism_det,
> +			purity_impure, [RegVar], [], [],
> +			ModuleInfo, Context, CallGoal)
> +	;
> +		unexpected(this_file, "region_instruction_to_conj: " ++
> +			"encounter unknown region instruction")
> +	),
> +	Conjs = Conjs0 ++ [CallGoal].
> +
> +	% A resurrection renaming annotation is in the form Rx = Rx_resur_y,
> +	% where Rx is the original name of the region, the other is the one
> +	% the region is renamed to.
> +	% This predicate converts the anotation into an assigment unification.
> +	% The original name of the region is subjected to the renaming due to
> +	% if-then-else, if such a renaming exists at the current program point.
> +	%
> +:- pred resur_renaming_annotation_to_assignment(renaming::in, string::in,
> +	name_to_prog_var::in, name_to_prog_var::out,
> +	prog_varset::in, prog_varset::out, vartypes::in, vartypes::out,
> +	hlds_goals::in, hlds_goals::out) is det.
> +
> +resur_renaming_annotation_to_assignment(IteRenaming, Annotation,
> +		!NameToVar, !VarSet, !VarTypes, Conjs0, Conjs) :-
> +	( if	string.sub_string_search(Annotation, "=", Index)
> +	  then
> +			Left = string.substring(Annotation, 0, Index - 1),
> +			Right = string.substring(Annotation, Index + 2,
> +				string.length(Annotation) - (Index + 2)),
> +			% Only the left region needs to be renamed. Ite renaming
> +			% does not involve one on the right side.
> +			region_name_to_var_with_renaming(Left, IteRenaming,
> +				LeftRegVar, !NameToVar, !VarSet, !VarTypes),
> +			region_name_to_var(Right, RightRegVar, !NameToVar,
> +				!VarSet, !VarTypes),
> +			make_assignment_goal(LeftRegVar, RightRegVar,
> +				"resurrection renaming annotation",
> +				AssignmentGoal),
> +			Conjs = Conjs0 ++ [AssignmentGoal]
> +	  else
> +			unexpected(this_file, "resur_renaming_annotation_to_assignment: "
> +				++ "annotation is not assigment")
> +	).
> +
> +	% This predicate turns a renaming annotation due to if-then-else into
> +	% an assignment. No renaming needs to be applied to the
> +	% if-then-else renaming annotations.
> +	%
> +:- pred ite_renaming_annotation_to_assignment(string::in,
> +	name_to_prog_var::in, name_to_prog_var::out,
> +	prog_varset::in, prog_varset::out, vartypes::in, vartypes::out,
> +	hlds_goals::in, hlds_goals::out) is det.
> +
> +ite_renaming_annotation_to_assignment(Annotation, !NameToVar,
> +		!VarSet, !VarTypes, Conjs0, Conjs) :-
> +	( if	string.sub_string_search(Annotation, "=", Index)
> +	  then
> +			Left = string.substring(Annotation, 0, Index - 1),
> +			Right = string.substring(Annotation, Index + 2,
> +				string.length(Annotation) - (Index + 2)),
> +			region_name_to_var(Left, LeftRegVar, !NameToVar,
> +				!VarSet, !VarTypes),
> +			region_name_to_var(Right, RightRegVar, !NameToVar,
> +				!VarSet, !VarTypes),
> +			make_assignment_goal(LeftRegVar, RightRegVar,
> +				"ite renaming annotation", AssignmentGoal),
> +			Conjs = Conjs0 ++ [AssignmentGoal]
> +	  else
> +			unexpected(this_file, "ite_renaming_annotation_to_assignment: "
> +				++ "annotation is not assignment")
> +	).
> +
> +:- pred make_assignment_goal(prog_var::in, prog_var::in, string::in,
> +	hlds_goal::out) is det.
> +
> +make_assignment_goal(LeftRegVar, RightRegVar, Context, AssignmentGoal) :-
> +	AssignmentExpr = unify(LeftRegVar, rhs_var(RightRegVar),
> +		out_mode - in_mode,
> +		assign(LeftRegVar, RightRegVar),
> +		unify_context(
> +			umc_implicit(Context),
> +			[]
> +		)
> +	),
> +	% Nonlocals and instmap delta will be recomputed anyway, so just put
> +	% dummy values in.
> +	NonLocals = set.init,
> +	instmap_delta_from_assoc_list([], InstmapDelta),
> +	goal_info_init(NonLocals, InstmapDelta, detism_det, purity_pure,
> +		AssignmentInfo),
> +	AssignmentGoal = hlds_goal(AssignmentExpr, AssignmentInfo).
> +

...

> +%-----------------------------------------------------------------------------%
> +%
> +% Recheck purity.
> +%
> +
> +:- pred check_purity_pred(pred_id::in, module_info::in,
> +	module_info::out) is det.
> +
> +check_purity_pred(PredId, !ModuleInfo) :-
> +    module_info_pred_info(!.ModuleInfo, PredId, PredInfo),
> +    ProcIds = pred_info_non_imported_procids(PredInfo),
> +	list.foldl(check_purity_proc(PredId), ProcIds, !ModuleInfo).
> +
> +	% Recheck purity of the procedure.
> +	% This predicate is only called when all the procedures have been
> +	% annotated with region information and recorded. This is necessary
> +	% because repuritycheck_proc looks up information
> +	% about procedures.
> +	%
> +:- pred check_purity_proc(pred_id::in, proc_id::in, module_info::in,
> +	module_info::out) is det.
> +
> +check_purity_proc(PredId, ProcId, !ModuleInfo) :-
> +	module_info_pred_info(!.ModuleInfo, PredId, PredInfo0),
> +	% Recheck purity of this procedure.
> +	PPId = proc(PredId, ProcId),
> +	repuritycheck_proc(!.ModuleInfo, PPId, PredInfo0, PredInfo),
> +	module_info_set_pred_info(PredId, PredInfo, !ModuleInfo).
> +

I suggest calling the above predicates: recheck_purity_pred and
recheck_purity_proc.

...

> Index: rbmm.actual_region_arguments.m
> ===================================================================
> RCS file:
> /home/mercury/mercury1/repository/mercury/compiler/rbmm.actual_region_arguments.m,v
> retrieving revision 1.1
> diff -u -u -r1.1 rbmm.actual_region_arguments.m
> --- rbmm.actual_region_arguments.m	8 Jun 2007 06:45:11 -0000	1.1
> +++ rbmm.actual_region_arguments.m	27 Jun 2007 07:35:21 -0000
> @@ -31,14 +31,23 @@
>
> :- import_module list.
> :- import_module map.
> +:- import_module pair.
>
> -:- type proc_pp_region_list_table == map(pred_proc_id, pp_region_list_table).
> -
> -:- type pp_region_list_table == map(program_point, list(rptg_node)).
> +:- type proc_pp_pair_region_list_table
> +    ==  map(
> +                pred_proc_id,
> +                pp_pair_region_list_table
> +        ).
> +
> +:- type pp_pair_region_list_table
> +    ==  map(
> +                program_point,
> +                pair(list(rptg_node), list(rptg_node))

I take it the first element of the pair is the inputs and the second
the outputs.  There should be a comment explaining this.

...

> @@ -238,9 +249,9 @@
>         LActualBornR0),
> 	list.reverse(LActualBornR0, LActualBornR),
>
> -    % Record in the order: constants, deads, and borns.
> -	L = LActualConstantR ++ LActualDeadR ++ LActualBornR,
> -    svmap.det_insert(CallSite, L, !ActualRegionArgProc).
> +    % Record in the order: (constants, deads) and borns.
> +	Ins = LActualConstantR ++ LActualDeadR,
> +    svmap.det_insert(CallSite, Ins - LActualBornR, !ActualRegionArgProc).

I don't understand the above coment.

I'm happy for you to commit this after the above comments are addressed
and this change has bootchecked.  As I mentioned in my last set of 
review comments (and we discussed in person) the representation of region
instructions should not be a string; you can fix that as a separate
change.  Also, I think the above code unnecessarily traverses the HLDS
in some places and that the whole region renaming thing can either
be simplified (or possible avoided altogether); looking into these
matters is a separate change.

Julien.



--------------------------------------------------------------------------
mercury-reviews mailing list
Post messages to:       mercury-reviews at csse.unimelb.edu.au
Administrative Queries: owner-mercury-reviews at csse.unimelb.edu.au
Subscriptions:          mercury-reviews-request at csse.unimelb.edu.au
--------------------------------------------------------------------------



More information about the reviews mailing list