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

Julien Fischer juliensf at csse.unimelb.edu.au
Fri Jun 22 18:18:28 AEST 2007


Hi Quan,

I haven't finished reviewing this yet, but here are some initial
comments.

> Estimated hours taken: 25.
> Branch: main.
>
> Annotate the HLDS with information about regions. This includes calls to
> region builtins, extra region arguments for procedures and calls, regions
> for construction unifications.

For a change of this size the log message should go into more detail

> 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/quantification.m
> compiler/structure_reuse.indirect.m
> 	Change to suit with the above additional type constructor.
>
> 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.
>
> compiler/rbmm.execution_path.m:
> 	Correct a typo.
>
> compiler/rbmm.m: Add a new submodule region_transformation.
>
> 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.

...

> Index: hlds_goal.m
> ===================================================================
> RCS file: /home/mercury/mercury1/repository/mercury/compiler/hlds_goal.m,v
> retrieving revision 1.177
> diff -u -u -r1.177 hlds_goal.m
> --- hlds_goal.m	13 Apr 2007 04:56:39 -0000	1.177
> +++ hlds_goal.m	8 Jun 2007 06:51:38 -0000
> @@ -764,12 +764,15 @@
> :- type how_to_construct
>     --->    construct_statically(
>                 % Use a statically initialized constant.
> -
>                 args :: list(static_cons)
>             )
> +
>     ;       construct_dynamically
>             % Allocate a new term on the heap
>
> +    ;
> +            construct_in_region(prog_var)

Add a comment describing this alternative.

...

> Index: quantification.m
> ===================================================================
> RCS file: /home/mercury/mercury1/repository/mercury/compiler/quantification.m,v
> retrieving revision 1.116
> diff -u -u -r1.116 quantification.m
> --- quantification.m	12 Jun 2007 07:21:25 -0000	1.116
> +++ quantification.m	18 Jun 2007 12:37:41 -0000
> @@ -517,6 +517,8 @@
>         ;
>             ( How = construct_statically(_)
>             ; How = construct_dynamically
> +            % XXX Temporary for the time being.
> +            ; How = construct_in_region(_)
>             ),
>             MaybeSetArgs = no,
>             MaybeReuseVar = no

You need to handle the region_variable in construct_in_region/1
like reuse vars are handled for the reuse case, i.e. the region variable
should be part of the non-local set.

> @@ -1129,6 +1131,8 @@
>         ;
>             ( How = construct_statically(_)
>             ; How = construct_dynamically
> +            % XXX Temporary for the time being.
> +            ; How = construct_in_region(_)
>             ),
>             MaybeSetArgs = no
>         ),

Similarly here.

> 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	18 Jun 2007 07:46:31 -0000

...

> +:- pred apply_renaming(rpt_graph::in, renaming::in, rptg_node::in,
> +	set(string)::in, set(string)::out) is det.
> +
> +apply_renaming(Graph, Renaming, Node, !Regions) :-
> +	RegionName = rptg_lookup_region_name(Graph, Node),
> +	( if	map.search(Renaming, RegionName, RenamedRegionName)
> +	  then	svset.insert(RenamedRegionName, !Regions)
> +	  else	svset.insert(RegionName, !Regions)
> +	).

The name of that predicate is too general; I would call it something
like apply_region_renaming.

...

> Index: rbmm.m
> ===================================================================
> RCS file: /home/mercury/mercury1/repository/mercury/compiler/rbmm.m,v
> retrieving revision 1.4
> diff -u -u -r1.4 rbmm.m
> --- rbmm.m	15 Jun 2007 11:46:11 -0000	1.4
> +++ rbmm.m	18 Jun 2007 07:32:48 -0000
>
> +	region_transform(RptaInfoTable, ConstantRTable, DeadRTable, BornRTable,
> +		ActualRegionArgumentTable, ResurRenamingTable, IteRenamingTable,
> +		AnnotationTable, ResurRenamingAnnoTable, IteRenamingAnnoTable,
> +		map.init, _NameToVarTable, !.ModuleInfo, Module),
> +	write_hlds(2, Module, !IO).

Why are you calling write_hlds here?  Invoking the compiler with
--dump-hlds=<rbmm stage #> ought to have the same effect.

> Index: rbmm.region_resurrection_renaming.m
> ===================================================================
> RCS file:
> /home/mercury/mercury1/repository/mercury/compiler/rbmm.region_resurrection_renaming.m,v
> retrieving revision 1.2
> diff -u -u -r1.2 rbmm.region_resurrection_renaming.m
> --- rbmm.region_resurrection_renaming.m	15 Jun 2007 11:46:12 -0000	1.2
> +++ rbmm.region_resurrection_renaming.m	18 Jun 2007 07:49:45 -0000

...

> @@ -572,15 +587,20 @@
>     svmap.det_insert(RegionName, NewName, !Renaming),
>
>     % Add annotation to (after) the previous program point.
> -    % Annotations are only added for resurrected regions that have been
> +    % XXX Annotations are only added for resurrected regions that have been
>     % renamed in this execution path (i.e., the execution path contains
>     % PrevProgPoint and ProgPoint).
> +    % It seems that we have to add annotations (reverse renaming) for
> +    % ones that have not been renamed too. The only difference is that
> +    % the reverse renaming is between the new name and the original name.
>     ( if    map.search(PrevRenaming, RegionName, CurrentName)
>       then
>             Annotation = NewName ++ " = " ++ CurrentName,
>             record_annotation(PrevProgPoint, Annotation, !AnnotationProc)
>       else
> -            true
> +            Annotation = NewName ++ " = " ++ RegionName,
> +            record_annotation(PrevProgPoint, Annotation, !AnnotationProc)
> +            %true
>     ).

Why the commented out bit at the end?



> 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	18 Jun 2007 06:46:46 -0000
> @@ -0,0 +1,944 @@

...

> +:- type name_to_prog_var_table == map(pred_proc_id, name_to_prog_var).
> +:- type name_to_prog_var == map(string, prog_var).

What are these types used for?  Document them.

> +
> +	% 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_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).
> +
> +	% 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
> +	  		module_info_pred_info(!.ModuleInfo, PredId, PredInfo0),
> +	  		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(PredInfo0),
> +			pred_info_set_orig_arity(Arity + NumberOfRegArgs,
> +				PredInfo0, PredInfo1),
> +
> +			generate_list_of_region_type(NumberOfRegArgs,
> +				make_region_type, RegionTypes),
> +			pred_info_get_arg_types(PredInfo1, TypeVarSet,
> +				ExistQuantTVars, ArgTypes0),
> +			PredOrFunc = pred_info_is_pred_or_func(PredInfo1),
> +			(
> +				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, PredInfo1, PredInfo2),
> +			module_info_set_pred_info(PredId, PredInfo2,
> +				!ModuleInfo),
> +			!:Processed = [PredId | !.Processed]

It would be better to use state variables to pass around the
PredInfo in the above code, e.g.

 	else
 		some [!PredInfo] (
  			module_info_pred_info(!.ModuleInfo, PredId,
 				!:PredInfo),
 		...

 			module_info_set_pred_inof(PredId, !.PredInfo,
 				!ModuleInfo)
 		),
 		!:Processed = [PredId | !.Processed]


> +:- pred generate_list_of_region_type(int::in, mer_type::in,
> +	list(mer_type)::out) is det.
> +
> +generate_list_of_region_type(N, RegType, RegTypes) :-
> +	( if	N = 0
> +	  then
> +	  	    RegTypes = []
> +	  else
> +			generate_list_of_region_type(N - 1, RegType, RegTypes0),
> +			RegTypes = [RegType | RegTypes0]
> +	).


Fix the indentation.


> +
> +	% 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_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.
> +	%
> +:- 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_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, PredInfo, 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, PredInfo, Graph, ConstantR, DeadR, BornR,
> +		ActualRegionArgProc, ResurRenamingProc, IteRenamingProc,
> +		AnnotationProc, ResurRenamingAnnoProc, IteRenamingAnnoProc,
> +		VarSet0, _, VarTypes0, _, HeadVars0, _, ActualArgModes0, _,
> +		Goal0, _, NameToVar0, NameToVar, ProcInfo1, ProcInfo),
> +
> +	module_info_set_pred_proc_info(PPId, PredInfo, 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
> +	%
> +	% XXX What about head_var_caller_liveness and
> +	% prog_sub_info -> arg_pass_info
> +	%
> +	%
> +:- pred annotate_proc(module_info::in, pred_info::in, rpt_graph::in,
> +	region_set::in, region_set::in, region_set::in,
> +	pp_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.
> +	% 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_reg_var(Graph), FormalNodes, FormalRegionArgs,
> +		!NameToVar, !VarSet, !VarTypes),
> +
> +	% Computing actual_head_modes.
> +	InMode = in_mode,
> +	OutMode = out_mode,
> +	list.foldl(generate_mode_list(InMode), FormalInputNodes, [], InModes),
> +	list.foldl(generate_mode_list(OutMode), LBornR, [], 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).
> +
> +:- pred generate_mode_list(mer_mode::in, rptg_node::in, list(mer_mode)::in,
> +	list(mer_mode)::out) is det.
> +
> +generate_mode_list(Mode, _Node, Modes0, [Mode | Modes0]).
> +
> +	% Basically, we will turn this atomic goal and all the region
> +	% annotations attached to (before and after) it into a
> +	% conjunction (even when there is no annotation). 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_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, Info),
> +	(	goal_is_atomic(GoalExpr0)
> +	->
> +		ProgPoint = program_point_init(Info),
> +		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(Graph, ResurRenaming,
> +			IteRenaming, ActualRegionArgProc, ProgPoint,
> +			GoalExpr0, GoalExpr, !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),
> +
> +		!:Goal = hlds_goal(conj(plain_conj, Conjs), Info)
> +	;
> +		region_transform_compound_goal(ModuleInfo, Graph,
> +			ResurRenamingProc, IteRenamingProc, ActualRegionArgProc,
> +			AnnotationProc, ResurRenamingAnnoProc,
> +			IteRenamingAnnoProc, !Goal, !NameToVar, !VarSet,
> +			!VarTypes)
> +	).
> +
> +:- pred region_transform_goal_expr(rpt_graph::in, renaming::in,
> +	renaming::in, pp_region_list_table::in, program_point::in,
> +	hlds_goal_expr::in, hlds_goal_expr::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, !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 = []
> +	),
> +	list.map_foldl3(node_to_reg_var_with_both_renamings(Graph,
> +		ResurRenaming, IteRenaming),
> +		ActualNodes, 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(Graph, ResurRenaming, IteRenaming,
> +		_, _, !GoalExpr, !NameToVar, !VarSet, !VarTypes) :-
> +	!.GoalExpr = unify(LHS, RHS, Mode, Unification0, Context),
> +    annotate_constructions_unification(Graph, ResurRenaming, IteRenaming,
> +		Unification0, Unification, !NameToVar, !VarSet, !VarTypes),
> +	!:GoalExpr = unify(LHS, RHS, Mode, Unification, Context).
> +
> +region_transform_goal_expr(_, _, _, _, _, !GoalExpr, !NameToVar,
> +		!VarSet, !VarTypes) :-
> +	!.GoalExpr = generic_call(_, _, _, _),
> +	sorry(this_file,
> +		"region_transform_goal_expr: generic call is not handled.").
> +
> +region_transform_goal_expr(_, _, _, _, _, !GoalExpr, !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, !NameToVar,
> +		!VarSet, !VarTypes) :-
> +	( !.GoalExpr = conj(_, [])
> +	; !.GoalExpr = disj([])
> +	).
> +
> +region_transform_goal_expr(_, _, _, _, _, !GoalExpr, !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.
> +	% For switch,

For switch, ?

> +:- pred region_transform_compound_goal(module_info::in, rpt_graph::in,
> +	renaming_proc::in, renaming_proc::in, pp_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_conjunction(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")
> +	).
> +
> +:- pred annotate_constructions_unification(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(Graph, ResurRenaming, IteRenaming,
> +		!Unification, !NameToVar, !VarSet, !VarTypes) :-
> +	!.Unification = construct(Var, ConsId, Args, ArgModes, _HowToConstruct0,
> +		IsUnique, SubInfo),
> +	get_node_by_variable(Graph, Var, Node),
> +	Name = rptg_lookup_region_name(Graph, Node),
> +	name_to_reg_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(_, _)
> +		),
> +		true
> +	;
> +		!.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_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_conjunction([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
> +	).
> +
> +	% XXX This flatten predicate is copied and pasted from
> +	% prop_mode_constraints.m.
> +	%
> +    % flatten_conjunction(!Goals) flattens the conjunction Goals - that
> +    % is, moves the conjuncts from nested conjunctions into Goals.
> +    %
> +:- pred flatten_conjunction(hlds_goals::in, hlds_goals::out) is det.
> +
> +flatten_conjunction(!Goals) :-
> +    list.foldr(add_to_conjunction, !.Goals, [], !:Goals).

What is wrong with using goal_util.flatten_conj/2?

> +
> +    % add_to_conjunction(Goal, !Goals) adds Goal to the front of
> +    % the conjunction Goals. It keeps the conjunction flat, so
> +    % nested conjunctions are scrapped and their conjuncts prepended
> +    % to Goals.
> +    %
> +:- pred add_to_conjunction(hlds_goal::in, hlds_goals::in, hlds_goals::out)
> +    is det.
> +
> +add_to_conjunction(Goal, !Goals) :-
> +    ( Goal = hlds_goal(conj(plain_conj, SubGoals), _) ->
> +        list.append(SubGoals, !Goals)
> +    ;
> +        list.cons(Goal, !Goals)
> +    ).

That doesn't appear to set up the goal_info for the new conjunction.

> +:- pred node_to_reg_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_reg_var(Graph, Node, RegVar, !NameToVar, !VarSet,
> +		!VarTypes) :-
> +	RegName = rptg_lookup_region_name(Graph, Node),
> +	name_to_reg_var(RegName, RegVar, !NameToVar, !VarSet, !VarTypes).
> +
> +:- pred name_to_reg_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.
> +
> +name_to_reg_var(Name, RegVar, !NameToVar, !VarSet, !VarTypes) :-
> +	( if	map.search(!.NameToVar, Name, RegVar0)
> +	  then
> +			RegVar = RegVar0
> +	  else
> +			varset.new_named_var(!.VarSet, Name, RegVar, !:VarSet),

Call svvarset.new_named_var/4 threre.

> +			svmap.det_insert(RegVar, make_region_type, !VarTypes),
> +			svmap.det_insert(Name, RegVar, !NameToVar)
> +	).
> +
> +:- pred node_to_reg_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_reg_var_with_both_renamings(Graph, ResurRenaming, IteRenaming,
> +		Node, RegVar, !NameToVar, !VarSet, !VarTypes) :-
> +	RegName = rptg_lookup_region_name(Graph, Node),
> +	name_to_reg_var_with_both_renamings(RegName, ResurRenaming, IteRenaming,
> +		RegVar, !NameToVar, !VarSet, !VarTypes).
> +
> +:- pred name_to_reg_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.
> +
> +name_to_reg_var_with_renaming(Name0, ResurRenaming, RegVar,
> +		!NameToVar, !VarSet, !VarTypes) :-
> +	( if	map.search(ResurRenaming, Name0, Name1)
> +	  then
> +	  		Name = Name1
> +	  else
> +			Name = Name0
> +	),
> +	name_to_reg_var(Name, RegVar, !NameToVar, !VarSet, !VarTypes).
> +
> +	% Resurrection renaming will be applied first. If a renaming exists
> +	% for the name (therefore the name is changed to another name) then
> +	% ite renaming need not to be applied because actually it is not
> +	% applicable anymore.
> +:- pred name_to_reg_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.
> +
> +name_to_reg_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
> +			)
> +	),
> +	name_to_reg_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).
> +
> +:- 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.
> +
> +	% 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.
> +	%

Instructions should *not* be represented as strings.  You're using
a strongly-typed language, so use types!  e.g.

 	:- type region_instruction
 		--->	region_instruction(
 				ri_rule_num :: int,
 				ri_instr_kindg :: region_op,
 				ri_name :: ???
 			).

 	:- type region_op
 		--->	region_create
 		;	region_remove.

or something along those lines.  That would also mean that a lot if
the if-then-elses that occur in the following code could be turned into
switches.

...

> Index: structure_reuse.indirect.m
> ===================================================================
> RCS file:
> /home/mercury/mercury1/repository/mercury/compiler/structure_reuse.indirect.m,v
> retrieving revision 1.10
> diff -u -u -r1.10 structure_reuse.indirect.m
> --- structure_reuse.indirect.m	12 Jun 2007 07:21:26 -0000	1.10
> +++ structure_reuse.indirect.m	18 Jun 2007 12:50:00 -0000
> @@ -302,6 +302,8 @@
>             ;
>                 ( HowToConstruct = construct_dynamically
>                 ; HowToConstruct = reuse_cell(_)
> +                % XXX Temporary for the time being.
> +                ; HowToConstruct = construct_in_region(_)

It isn't clear which alternative the XXX comment is supposed to apply
there.

To be continued ...

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