[m-rev.] for review: implicit_parallelism and distance_granularity (new modules)

Julien Fischer juliensf at csse.unimelb.edu.au
Wed Dec 20 15:46:40 AEDT 2006


On Wed, 6 Dec 2006, Jerome Tannier wrote:

> Estimated hours taken: 80
> Branches: main
>
> This change adds two new passes to the compiler. The first one,
> implicit_parallelism, uses deep profiling feedback information, generated
> by mdprof_feedback, to introduce parallel conjunctions where it could be
> worthwhile. It deals with both independent and dependent parallelism.

> The second one, distance_granularity, apply a transformation to control the
> granularity of parallelism of recursive procedures using the distance
> metric.

I suggest:

 	The second new pass, distance_granularity, applies a transformation
 	that controls the granularity of parallelism for recursive procedures
 	using the distance metric.

Briefly mention the third major change in this diff - it fixes a bug in
mdprof_feedback.  Also, the list of file specific changes should be
reorderd so that the major ones are mentioned first.

> compiler/dep_par_conj.m:
> 	Moved find_shared_variables in the interface (needed for 
> implicit_parallelism.m).
>
> compiler/distance_granularity.m:
> 	New module which controls the granularity of parallelism using the 
> distance
> 	metric.

I suggest

 	New module.  A program transformation that implements granularity
 	control of parallel execution using the distance metric.

> compiler/goal_util.m:
> 	Add two new predicates: flatten_conj and create_conj.
>
> compiler/hhf.m:
> 	Delete flatten_conj and use the one of goal_util instead.
>
> compiler/hlds_pred.m:
> 	Add a predicate to set the arity of a predicate (needed for 
> distance_granularity).
>
> compiler/implicit_parallelism.m:
> 	New module which reads the profiling feedback file and decides where 
> parallelism 		should be introduced.

Specifically, it uses profiling feedback to introduce parallel conjunction.

> compiler/mercury_compile.m:
> 	Add the calls to apply implicit parallelism and to control 
> granularity using the
> 	distance metric.
>
> compiler/options:
> 	Add implicit-parallelism, feedback-file and distance-granularity 
> options.

These also need to be documented in the user's guide.

> compiler/pred_table.m:
> 	Add a predicate to get the next pred_id available (needed for
> 	distance_granularity).
>
> compiler/prog_util.m:
> 	Extend the predicate make_pred_name and the type new_pred_id for
> 	creating a predicate name for distance_granularity.
>
> compiler/transform_hlds.m:
> 	Add transform_paralellism and distance_granularity in the included 
> modules.

s/Add/Include/

> deep_profiler/dump.m:
> 	Add "all" option to dump everything out of the Deep.data file.
>
> deep_profiler/mdprof_feedback.m:
> 	Rename distribution to measure.
> 	Add handling of dump_stages and dump_options.
> 	Correct the way the list of CSS is built (elems were put in the wrong 
> order).

 	Insert elements into the list of CSSs in the correct order.

Can you also please add some test cases that use the distance granularity
transformation to the test suite?

...

> Index: compiler/dep_par_conj.m
> ===================================================================
> RCS file: /home/mercury1/repository/mercury/compiler/dep_par_conj.m,v
> retrieving revision 1.15
> diff -u -r1.15 dep_par_conj.m
> --- compiler/dep_par_conj.m	5 Dec 2006 03:50:49 -0000	1.15
> +++ compiler/dep_par_conj.m	6 Dec 2006 05:57:34 -0000
> @@ -64,15 +64,23 @@
> :- module transform_hlds.dep_par_conj.
> :- interface.
>

...

> :- pred dependent_par_conj(module_info::in, module_info::out, io::di, 
> io::uo)
>     is det.
>
> +    %Used by transform_hlds.implicit_parallelism.

I suggest:

 	Exported for use by the implicit_parallism pass.

...

> Index: compiler/distance_granularity.m
> ===================================================================
> RCS file: compiler/distance_granularity.m
> diff -N compiler/distance_granularity.m
> --- /dev/null	1 Jan 1970 00:00:00 -0000
> +++ compiler/distance_granularity.m	6 Dec 2006 05:57:34 -0000

...

> +% File: distance_granularity.m.
> +% Author: tannier.
> +%
> +% This module controls the granularity of parallelism at compile time using 
> the
> +% distance metric.

I suggest:

 	This module contains a program transformation that adds a
 	mechanism that controls the granularity of parallel execution
 	using the distance metric.

>    For more information, see:
> +% K. Shen, V. Santos Costa, and A. King.
> +% Distance: a New Metric for Controlling Granularity for Parallel Execution.
> +% In Proceedings of the Joint International Conference and Symposium on 
> Logic
> +% Programming.
> +% MIT Press, 1998.
> +% http://www.cs.ukc.ac.uk/pubs/1998/588.
> +% http://citeseer.ist.psu.edu/shen98distance.html.
> +%
> +% Example of the transformation:
> +%
> +% From the originial version of fibonacci:

s/originial/original/

> +%
> +% :- pred fibonacci(int::in, int::out) is det.
> +%
> +% fibonacci(X, Y) :-
> +%     ( X = 0 ->
> +%         Y = 0
> +%     ;
> +%         ( X = 1 ->
> +%             Y = 1
> +%         ;
> +%             ( X > 1 ->
> +%                 J = X - 1,
> +%                 K = X - 2,
> +%                 (
> +%                     fibonacci(J, Jout)
> +%                 &
> +%                     fibonacci(K, Kout)
> +%                 ),
> +%                 Y = Jout + Kout
> +%             ;
> +%                 error("fibonacci: wrong value")
> +%             )
> +%         )
> +%     ).
> +%
> +% we create a specialized/cloned version (we assume that the distance which

Choose one of "specialized" or "cloned" and stick with it rather than
continually writing specialized/cloned.  (I suggest specialized.)

> was
> +% given during compilation is 10):
> +%
> +% :- pred ditance_granularity_fibonacci(int::in, int::out, int::in) is det.

s/ditance_/distance_/

> +%
> +% distance_granularity_fibonacci(X, Y, Distance) :-
> +%     ( X = 0 ->
> +%         Y = 0
> +%     ;
> +%         ( X = 1 ->
> +%             Y = 1
> +%         ;
> +%             ( X > 1 ->
> +%                 J = X - 1,
> +%                 K = X - 2,
> +%                 ( Distance = 0 ->
> +%                     (
> +%                         distance_granularity_fibonacci(J, Jout, 10)
> +%                     &
> +%                         distance_granularity_fibonacci(K, Kout, 10)
> +%                     )
> +%                 ;
> +%                     distance_granularity_fibonacci(J, Jout, Distance - 1),
> +%                     distance_granularity_fibonacci(K, Kout, Distance - 1)
> +%                 ),
> +%                 Y = Jout + Kout
> +%             ;
> +%                 error("fibonacci: wrong value")
> +%             )
> +%         )
> +%     ).
> +%
> +% After wich, the original version becomes:

s/wich/which/

> +%
> +% :- pred fibonacci(int::in, int::out) is det.
> +%
> +% fibonacci(X, Y) :-
> +%     ( X = 0 ->
> +%         Y = 0
> +%     ;
> +%         ( X = 1 ->
> +%             Y = 1
> +%         ;
> +%             ( X > 1 ->
> +%                 J = X - 1,
> +%                 K = X - 2,
> +%                 (
> +%                     distance_granularity_fibonacci(J, Jout, 10)
> +%                 %
> +%                     distance_granularity_fibonacci(K, Kout, 10)
> +%                 ),
> +%                 Y = Jout + Kout
> +%             ;
> +%                 error("fibonacci: wrong value")
> +%             )
> +%         )
> +%     ).
> +%
> +% The second part of the transformation makes the granularity control
> +% transparent to the user (there is no need to call explicitly the specified
> +% version of the recursive predicate).

I suggest:

 	The second part of the transformation makes the granularity control
 	transparent to the original procedure's callers by replacing the
 	recursive calls in the body of the original procedure with calls to
 	the specialized version.  The original procedure's callers should
 	never need to call the specialized version directly.

> +% XXX For the time being, we assume that the int module was imported in the
> +% source code of the program for which we apply the distance granularity
> +% transformation.

That's easily fixed but can be done as part of separate change.

> +%-----------------------------------------------------------------------------%
> +
> +:- module transform_hlds.distance_granularity.
> +:- interface.
> +
> +:- import_module hlds.hlds_module.
> +
> +%-----------------------------------------------------------------------------%
> +
> +    % control_distance_granularity(!ModuleInfo, Distance)
> +    %
> +    % Control the granularity of parallelism of a module using the distance
> +    % metric.
> +    %
> +:- pred control_distance_granularity(module_info::in, module_info::out,
> +    int::in) is det.

...

> +    % This section contains predicates which apply the first part of the
> +    % transformation i.e. creating the specialized/cloned version of the
> +    % original predicate.
> +
> +
> +control_distance_granularity(!ModuleInfo, Distance) :-
> +    module_info_predids(!.ModuleInfo, PredIds),
> +    apply_dg_to_preds(PredIds, Distance, !ModuleInfo).
> +
> +    % Apply the distance granularity transformation to a each predicate in 
> the
> +    % list.


s/to a each/to each/

> +    %
> +:- pred apply_dg_to_preds(list(pred_id)::in, int::in,
> +    module_info::in, module_info::out) is det.
> +
> +apply_dg_to_preds([], _Distance, !ModuleInfo).
> +apply_dg_to_preds([PredId | PredIdList], Distance, !ModuleInfo) :-
> +    module_info_pred_info(!.ModuleInfo, PredId, PredInfo),
> +    % We need to know what the pred_id will be for the cloned predicate 
> before
> +    % we actually clone it (this avoid doing one more pass to update the

s/avoid/avoids/

> pred_id
> +    % in the recursive plain calls).
> +    module_info_get_predicate_table(!.ModuleInfo, PredicateTable),
> +    get_next_pred_id(PredicateTable, NewPredId),
> +
> +    % Create the new sym_name for the recursive plain calls.
> +    ModuleName = pred_info_module(PredInfo),
> +    Prefix = granularity_prefix,
> +    PredOrFunc = pred_info_is_pred_or_func(PredInfo),
> +    MaybePredOrFunc = yes(PredOrFunc),
> +    NewPredIdGranularity = newpred_distance_granularity(Distance),
> +    PredName0 = pred_info_name(PredInfo),
> +    make_pred_name(ModuleName, Prefix, MaybePredOrFunc, PredName0,
> +        NewPredIdGranularity, NewCallSymName),
> +
> +    ProcIds = pred_info_non_imported_procids(PredInfo),
> +    apply_dg_to_procs(PredId, ProcIds, Distance, PredOrFunc, NewPredId,
> +        NewCallSymName, PredInfo, PredInfoClone0, no, Cloned, !ModuleInfo),
> +    (
> +        Cloned = yes,
> +        % The predicate has been cloned as it contains recursive calls.
> +
> +        % Update the name of the predicate.

You're not actually updating anything are you?  You're creating the name
of the specialised version of the predicate out of the name of the original
one.

> +        update_pred_name(Prefix, PredOrFunc, Distance, PredName0, PredName),
> +        pred_info_set_name(PredName, PredInfoClone0, PredInfoClone1),
> +
> +        % The arity and the argument types of the cloned procedure must be
> +        % modified.
> +        Arity = pred_info_orig_arity(PredInfoClone1),
> +        pred_info_set_orig_arity(Arity + 1, PredInfoClone1, PredInfoClone2),
> +        pred_info_get_arg_types(PredInfoClone2, ListMerType0),

s/ListMerType/ArgTypes/

> +        (
> +            PredOrFunc = predicate,
> +            % The argument controlling the granularity is the last one.
> +            list.append(ListMerType0, [int_type], ListMerType)
> +        ;
> +            PredOrFunc = function,
> +            % The argument controlling the granularity is the second last 
> one.
> +            list.length(ListMerType0, LengthListMerType),
> +            list.det_split_list(LengthListMerType - 1, ListMerType0,
> +                StartListMerType0, EndListMerType),
> +            list.append(StartListMerType0, [int_type], StartListMerType),
> +            list.append(StartListMerType, EndListMerType, ListMerType)


As we discussed in person all this mucking around with function return
values can be avoided by just making sure that the specialized version of
the procedure is always a predicate, even if the original was a function.
Since all calls to the specialised procedure are going to be made via the
(transformed version of) the original procedure it doesn't matter if the
specialised procedure is a function or a predicate.  Restricting it to
always be a predicate should simplify matters.

> +        pred_info_get_typevarset(PredInfoClone2, Tvarset),
> +        pred_info_get_exist_quant_tvars(PredInfoClone2, ExistqTvars),
> +        pred_info_set_arg_types(Tvarset, ExistqTvars, ListMerType,
> +            PredInfoClone2, PredInfoClone),
> +
> +        % Add the cloned predicate to the predicate table.
> +        module_info_get_predicate_table(!.ModuleInfo, PredicateTable0),
> +        predicate_table_insert(PredInfoClone, _, PredicateTable0,
> +            PredicateTable1),
> +        module_info_set_predicate_table(PredicateTable1, !ModuleInfo),
> +
> +        update_original_predicate_procs(PredId, ProcIds, Distance, 
> PredOrFunc,
> +            NewPredId, NewCallSymName, PredInfo, PredInfoUpdated, 
> !ModuleInfo),
> +        module_info_set_pred_info(PredId, PredInfoUpdated, !ModuleInfo)
> +    ;
> +        Cloned = no,
> +        % The predicate has not been cloned.
> +        true
> +    ),
> +    apply_dg_to_preds(PredIdList, Distance, !ModuleInfo).
> +
> +    % Apply the distance granularity transformation to each procedure in the
> +    % list.
> +    % PredIdSpecialized is the pred_id of the predicate to be cloned.
> +    % SymNameSpecialized is the sym_name of the predicate to be cloned.
> +    %
> +:- pred apply_dg_to_procs(pred_id::in, list(proc_id)::in, int::in,
> +    pred_or_func::in, pred_id::in, sym_name::in, pred_info::in, 
> pred_info::out,
> +    bool::in, bool::out, module_info::in, module_info::out) is det.
> +
> +apply_dg_to_procs(_PredId, [], _Distance, _PredOrFunc, _PredIdSpecialized,
> +        _SymNameSpecialized, !PredInfo, !Cloned, !ModuleInfo).
> +apply_dg_to_procs(PredId, [ProcId | ProcIds], Distance, PredOrFunc,
> +        PredIdSpecialized, SymNameSpecialized, !PredInfo, !Cloned,
> +        !ModuleInfo) :-
> +    module_info_proc_info(!.ModuleInfo, proc(PredId, ProcId), ProcInfo0),
> +    proc_info_get_has_parallel_conj(ProcInfo0, HasParallelConj),
> +    (
> +        HasParallelConj = yes,
> +        % The procedure contains parallel conjunction(s).
> +
> +        proc_info_get_goal(ProcInfo0, Body),
> +        apply_dg_to_goal(Body, BodyClone, PredId, ProcId, PredIdSpecialized,
> +            SymNameSpecialized, ProcInfo0, ProcInfo1, !ModuleInfo, Distance,
> +            PredOrFunc, no, no, GranularityVar, _),

s/GranularityVar/MaybeGranularityVar/

> +        (
> +            GranularityVar = yes(_),
> +            % The granularity variable has been created while the procedure 
> was
> +            % processed. That means that the predicate must be cloned.
> +            !:Cloned = yes,
> +            proc_info_set_goal(BodyClone, ProcInfo1, ProcInfo2),
> +            requantify_proc(ProcInfo2, ProcInfo3),
> +            RecomputeAtomic = no,
> +            recompute_instmap_delta_proc(RecomputeAtomic, ProcInfo3,
> +                ProcInfo, !ModuleInfo),
> +            pred_info_set_proc_info(ProcId, ProcInfo, !PredInfo)
> +        ;
> +            GranularityVar = no
> +        )
> +    ;
> +        HasParallelConj = no
> +        % No need to apply the distance granularity transformation to this
> +        % procedure as it does not contain any parallel conjunctions.
> +    ),
> +    apply_dg_to_procs(PredId, ProcIds, Distance, PredOrFunc, 
> PredIdSpecialized,
> +        SymNameSpecialized, !PredInfo, !Cloned, !ModuleInfo).
> +
> +    % Apply the distance granularity transformation to a goal.
> +    % CallerPredId and CallerProcId are those of the original predicate.
> +    %
> +:- pred apply_dg_to_goal(hlds_goal::in, hlds_goal::out, pred_id::in,
> +    proc_id::in, pred_id::in, sym_name::in, proc_info::in, proc_info::out,
> +    module_info::in, module_info::out, int::in, pred_or_func::in, bool::in,
> +    maybe(prog_var)::in, maybe(prog_var)::out, bool::out) is det.
> +
> +apply_dg_to_goal(!Goal, CallerPredId, CallerProcId, PredIdSpecialized,
> +        SymNameSpecialized, !ProcInfo, !ModuleInfo, Distance, PredOrFunc,
> +        IsInParallelConj, !MaybeGranularityVar,
> +        IsRecursiveCallInParallelConj) :-
> +    !.Goal = GoalExpr0 - GoalInfo,
> +    (
> +        GoalExpr0 = unify(_, _, _, _, _),
> +        IsRecursiveCallInParallelConj = no
> +    ;
> +        GoalExpr0 = plain_call(_, _, _, _, _, _),
> +        apply_dg_to_plain_call(GoalExpr0, GoalExpr, CallerPredId,
> +            PredIdSpecialized, SymNameSpecialized, CallerProcId, !ProcInfo,
> +            !ModuleInfo, PredOrFunc, IsInParallelConj, !MaybeGranularityVar,
> +            IsRecursiveCallInParallelConj),
> +        !:Goal = GoalExpr - GoalInfo
> +    ;
> +        GoalExpr0 = call_foreign_proc(_, _, _, _, _, _, _),
> +        IsRecursiveCallInParallelConj = no
> +    ;
> +        GoalExpr0 = generic_call(_, _, _, _),
> +        IsRecursiveCallInParallelConj = no
> +    ;
> +        GoalExpr0 = conj(Type, Goals0),
> +        apply_dg_to_conj(Goals0, [], Goals, CallerPredId, CallerProcId,
> +            PredIdSpecialized, SymNameSpecialized, !ProcInfo, !ModuleInfo,
> +            Distance, PredOrFunc, yes, !MaybeGranularityVar, no,
> +            ContainRecursiveCalls),
> +        (
> +            Type = plain_conj,
> +            GoalExpr = conj(plain_conj, Goals),
> +            !:Goal = GoalExpr - GoalInfo
> +        ;
> +            Type = parallel_conj,
> +            (
> +                ContainRecursiveCalls = yes,
> +                create_if_then_else_goal(Goals, GoalInfo, 
> !.MaybeGranularityVar,
> +                    PredIdSpecialized, CallerProcId, Distance, PredOrFunc,
> +                    !:Goal, !ProcInfo, !.ModuleInfo)
> +            ;
> +                ContainRecursiveCalls = no,
> +                true
> +            )
> +        ),
> +        IsRecursiveCallInParallelConj = no
> +    ;
> +        GoalExpr0 = disj(Goals0),
> +        apply_dg_to_disj(Goals0, [], Goals, CallerPredId, CallerProcId,
> +            PredIdSpecialized, SymNameSpecialized, !ProcInfo, !ModuleInfo,
> +            Distance, PredOrFunc, !MaybeGranularityVar),
> +        GoalExpr = disj(Goals),
> +        !:Goal = GoalExpr - GoalInfo,
> +        IsRecursiveCallInParallelConj = no
> +    ;
> +        GoalExpr0 = switch(Var, CanFail, Cases0),
> +        apply_dg_to_switch(Cases0, [], Cases, CallerPredId, CallerProcId,
> +            PredIdSpecialized, SymNameSpecialized, !ProcInfo, !ModuleInfo,
> +            Distance, PredOrFunc, !MaybeGranularityVar),
> +        GoalExpr = switch(Var, CanFail, Cases),
> +        !:Goal = GoalExpr - GoalInfo,
> +        IsRecursiveCallInParallelConj = no
> +    ;
> +        GoalExpr0 = negation(Goal0),
> +        apply_dg_to_goal(Goal0, Goal, CallerPredId, CallerProcId,
> +            PredIdSpecialized, SymNameSpecialized, !ProcInfo, !ModuleInfo,
> +            Distance, PredOrFunc, IsInParallelConj, !MaybeGranularityVar,
> +            IsRecursiveCallInParallelConj),
> +        GoalExpr = negation(Goal),
> +        !:Goal = GoalExpr - GoalInfo
> +    ;
> +        GoalExpr0 = scope(_, _),
> +        IsRecursiveCallInParallelConj = no

Why is the transformation not applied to the goal inside the scope?

> +    ;
> +        GoalExpr0 = if_then_else(Vars, If0, Then0, Else0),

s/If0/Cond0/ and likewise below.

> +        apply_dg_to_goal(If0, If, CallerPredId, CallerProcId, 
> PredIdSpecialized,
> +            SymNameSpecialized, !ProcInfo, !ModuleInfo, Distance, 
> PredOrFunc,
> +            no, !MaybeGranularityVar, _),
> +        apply_dg_to_goal(Then0, Then, CallerPredId, CallerProcId,
> +            PredIdSpecialized, SymNameSpecialized, !ProcInfo, !ModuleInfo,
> +            Distance, PredOrFunc, no, !MaybeGranularityVar, _),
> +        apply_dg_to_goal(Else0, Else, CallerPredId, CallerProcId,
> +            PredIdSpecialized, SymNameSpecialized, !ProcInfo, !ModuleInfo,
> +            Distance, PredOrFunc, no, !MaybeGranularityVar, _),
> +        GoalExpr = if_then_else(Vars, If, Then, Else),
> +        !:Goal = GoalExpr - GoalInfo,
> +        IsRecursiveCallInParallelConj = no

...

> +    % Apply the distance granularity transformation to a plain call.
> +    %
> +:- pred apply_dg_to_plain_call(hlds_goal_expr::in, hlds_goal_expr::out,
> +    pred_id::in, pred_id::in, sym_name::in, proc_id::in, proc_info::in,
> +    proc_info::out, module_info::in, module_info::out, pred_or_func::in,
> +    bool::in, maybe(prog_var)::in, maybe(prog_var)::out,
> +    bool::out) is det.
> +
> +apply_dg_to_plain_call(!CallExpr, CallerPredId, PredIdSpecialized,
> +        SymNameSpecialized, CallerProcId, !ProcInfo, !ModuleInfo, 
> PredOrFunc,
> +        IsInParallelConj, !MaybeGranularityVar,
> +        IsRecursiveCallInParallelConj) :-
> +    ( !.CallExpr = plain_call(CalleePredId, CalleeProcId, CallArgs, 
> CallBuiltin,
> +        CallUnifyContext, _) ->
> +        ( IsInParallelConj = yes, CalleePredId = CallerPredId,
> +            CalleeProcId = CallerProcId
> +        ->
> +            % That is a recursive plain call in a parallel conjunction.
> +            (
> +                !.MaybeGranularityVar = yes(_GranularityVar),
> +                % The variable Granularity has already been added to 
> ProcInfo.
> +                true
> +            ;
> +                !.MaybeGranularityVar = no,
> +                % Add the variable Granularity to ProcInfo.
> +                proc_info_create_var_from_type(int_type, no, GranularityVar,
> +                    !ProcInfo),
> +                !:MaybeGranularityVar = yes(GranularityVar),
> +
> +                % XXX Check if the int module is imported (that is why
> +                % ModuleInfo can be modified).
> +
> +                % Add the int variable to the head variables of the

s/int variable/granularity variable/ for consistency with the terminology
you use elsewhere.

> procedure
> +                % and adapt the mode.

s/adapt the mode/and update the argmodes/

> +                proc_info_get_argmodes(!.ProcInfo, ArgsModes0),
> +                proc_info_get_headvars(!.ProcInfo, HeadVars0),
> +                (
> +                    PredOrFunc = predicate,
> +                    % The argument controlling the granularity is the last 
> one.
> +                    list.append(ArgsModes0, [in_mode], ArgsModes),
> +                    list.append(HeadVars0, [GranularityVar], HeadVars)
> +                ;
> +                    PredOrFunc = function,
> +                    % The argument controlling the granularity is the second
> +                    % last one.
> +                    list.length(ArgsModes0, LengthArgsModes),
> +                    list.det_split_list(LengthArgsModes - 1, ArgsModes0,
> +                    StartArgsModes0, EndArgsModes),
> +                    list.append(StartArgsModes0, [in_mode], StartArgsModes),
> +                    list.append(StartArgsModes, EndArgsModes, ArgsModes),
> +
> +                    list.length(HeadVars0, LengthHeadVars),
> +                    list.det_split_list(LengthHeadVars - 1, HeadVars0,
> +                        StartHeadVars0, EndHeadVars),
> +                    list.append(StartHeadVars0, [GranularityVar],
> +                        StartHeadVars),
> +                    list.append(StartHeadVars, EndHeadVars, HeadVars)
> +                ),
> +                proc_info_set_argmodes(ArgsModes, !ProcInfo),
> +                proc_info_set_headvars(HeadVars, !ProcInfo)
> +            ),
> +
> +            % Change the pred_id and the sym_name. We will deal with the
> +            % arguments later as they are not identical for the then and the
> +            % else part of the if_then_else goal introduced by the
> +            % transformation.
> +            !:CallExpr = plain_call(PredIdSpecialized, CallerProcId,
> +                CallArgs, CallBuiltin, CallUnifyContext, 
> SymNameSpecialized),
> +            IsRecursiveCallInParallelConj = yes
> +        ;
> +            IsRecursiveCallInParallelConj = no
> +        )

...

> +    % Apply the distance granularity transformation to a conjunction.
> +    %
> +:- pred apply_dg_to_conj(hlds_goals::in, hlds_goals::in, hlds_goals::out,
> +    pred_id::in, proc_id::in, pred_id::in, sym_name::in,
> +    proc_info::in, proc_info::out, module_info::in, module_info::out, 
> int::in,
> +    pred_or_func::in, bool::in, maybe(prog_var)::in, maybe(prog_var)::out,
> +    bool::in, bool::out) is det.
> +
> +apply_dg_to_conj([], !GoalsAcc, _CallerPredId, _CallerProcId,
> +        _PredIdSpecialized, _SymNameSpecialized, !ProcInfo, !ModuleInfo,
> +        _Distance, _PredOrFunc, _IsInParallelConj,
> +        !MaybeGranularityVar, !HasRecursiveCallsInParallelConj).
> +apply_dg_to_conj([Goal0 | Goals], !GoalsAcc, CallerPredId, CallerProcId,
> +        PredIdSpecialized, SymNameSpecialized, !ProcInfo, !ModuleInfo,
> +        Distance, PredOrFunc, IsInParallelConj, !MaybeGranularityVar,
> +        !HasRecursiveCallsInParallelConj) :-
> +    apply_dg_to_goal(Goal0, Goal, CallerPredId, CallerProcId, 
> PredIdSpecialized,
> +        SymNameSpecialized, !ProcInfo, !ModuleInfo, Distance, PredOrFunc,
> +        IsInParallelConj, !MaybeGranularityVar, IsRecursiveCall),
> +    list.append(!.GoalsAcc, [Goal], !:GoalsAcc),
> +    (
> +        IsRecursiveCall = yes,
> +        % The goal we just processed is a recursive call in a parallel
> +        % conjunction. Therefore, the conjunction contains recursive calls.
> +        !:HasRecursiveCallsInParallelConj = yes
> +    ;
> +        IsRecursiveCall = no,
> +        !:HasRecursiveCallsInParallelConj = 
> !.HasRecursiveCallsInParallelConj
> +    ),
> +    apply_dg_to_conj(Goals, !GoalsAcc, CallerPredId, CallerProcId,
> +        PredIdSpecialized, SymNameSpecialized, !ProcInfo, !ModuleInfo, 
> Distance,
> +        PredOrFunc, IsInParallelConj, !MaybeGranularityVar,
> +        !HasRecursiveCallsInParallelConj).
> +
> +    % Create the if_then_else goal surrounding the recursive plain call as
> +    % showed in the example.

s/showed/shown/

> +    %
> +:- pred create_if_then_else_goal(hlds_goals::in, hlds_goal_info::in,
> +    maybe(prog_var)::in, pred_id::in, proc_id::in, int::in, 
> pred_or_func::in,
> +    hlds_goal::out, proc_info::in, proc_info::out, module_info::in) is det.
> +
> +create_if_then_else_goal(GoalsInConj, ConjInfo, MaybeGranularityVar,
> +        PredIdSpecialized, CallerProcId, Distance, PredOrFunc, 
> IfThenElseGoal,
> +        !ProcInfo, ModuleInfo) :-
> +    proc_info_create_var_from_type(int_type, no, Var, !ProcInfo),
> +    make_int_const_construction(Var, 0, UnifyGoal),
> +    (
> +        MaybeGranularityVar = yes(GranularityVar),
> +        % Create the if.

s/if./condition./

> +        make_simple_test(GranularityVar, Var,
> +            umc_implicit("distance_granularity"), [], Test),
> +        create_conj(UnifyGoal, Test, plain_conj ,If),
> +
> +        % Create the then.
> +        Then0 = conj(parallel_conj, GoalsInConj) - ConjInfo,
> +        apply_dg_to_then(Then0, Then, GranularityVar, PredIdSpecialized,
> +            CallerProcId, Distance, PredOrFunc, !ProcInfo),
> +
> +        % Create the else.
> +        Else0 = conj(plain_conj, GoalsInConj) - ConjInfo,
> +        apply_dg_to_else(Else0, Else, GranularityVar, PredIdSpecialized,
> +            CallerProcId, ModuleInfo, PredOrFunc, !ProcInfo),
> +
> +        % The non locals of the hlds_goal_info of the if_then_else goal must

s/non locals/non-locals/

> +        % contain the variable controlling the granularity.
> +        goal_info_get_nonlocals(ConjInfo, NonLocals0),
> +        set.insert(NonLocals0, GranularityVar, NonLocals),
> +        goal_info_set_nonlocals(NonLocals, ConjInfo, IfThenElseInfo),
> +        IfThenElseGoal = if_then_else([], If, Then, Else) - IfThenElseInfo
> +    ;
> +        MaybeGranularityVar = no,
> +        % The conjunction contains recursive calls so the
> +        % granularity variable must have been created.
> +        unexpected(this_file, "apply_dg_to_goal")
> +    ).
> +
> +    % Update the then part of the new if_then_else goal introduced by the
> +    % transformation as showed in the example. It creates a variable

s/showed/shown/

> Granularity
> +    % containing the value Distance and uses it as the last argument of the
> +    % recursive calls.
> +    %
> +:- pred apply_dg_to_then(hlds_goal::in, hlds_goal::out, prog_var::in,
> +    pred_id::in, proc_id::in, int::in, pred_or_func::in,
> +    proc_info::in, proc_info::out) is det.
> +
> +apply_dg_to_then(!Goal, GranularityVar, CallerPredId, CallerProcId, 
> Distance,
> +        PredOrFunc, !ProcInfo) :-
> +    !.Goal = GoalExpr0 - GoalInfo,
> +    apply_dg_to_then2(GoalExpr0, GoalExpr, 1, _, GranularityVar, 
> CallerPredId,
> +        CallerProcId, Distance, PredOrFunc, !ProcInfo),
> +    Goal0 = GoalExpr - GoalInfo,
> +    recompute_conj_info(Goal0, !:Goal).
> +
> +:- pred apply_dg_to_then2(hlds_goal_expr::in, hlds_goal_expr::out,
> +    int::in, int::out, prog_var::in, pred_id::in, proc_id::in, int::in,
> +    pred_or_func::in, proc_info::in, proc_info::out) is det.
> +
> +apply_dg_to_then2(!GoalExpr, !IndexInConj, GranularityVar, CallerPredId,
> +        CallerProcId, Distance, PredOrFunc, !ProcInfo) :-
> +    ( !.GoalExpr = conj(parallel_conj, Goals0) ->
> +        list.length(Goals0, Length),
> +        ( !.IndexInConj > Length ->
> +            true
> +        ;
> +            list.index1_det(Goals0, !.IndexInConj, Goal0),
> +            Goal0 = GoalExpr0 - GoalInfo0,
> +            ( GoalExpr0 = plain_call(CalleePredId, CalleeProcId, CallArgs0,
> +                CallBuiltin, CallUnifyContext, CallSymName)
> +            ->
> +                ( CalleePredId = CallerPredId, CalleeProcId = CallerProcId 
> ->
> +                    % That is a recursive plain call.
> +
> +                    % Create int variable containing value Distance.

Likewise: s/int variable/granularity variable/

...

> +:- pred recompute_conj_info(hlds_goal::in, hlds_goal::out) is det.
> +
> +recompute_conj_info(!Conj) :-
> +    ( !.Conj = conj(Type, Goals) - ConjInfo0 ->
> +        goal_list_nonlocals(Goals, NonLocals),
> +        goal_list_instmap_delta(Goals, InstMapDelta),
> +        goal_list_determinism(Goals, Detism),
> +        goal_list_purity(Goals, Purity),
> +        goal_info_set_nonlocals(NonLocals, ConjInfo0, ConjInfo1),
> +        goal_info_set_instmap_delta(InstMapDelta, ConjInfo1, ConjInfo2),
> +        goal_info_set_determinism(Detism, ConjInfo2, ConjInfo3),
> +        goal_info_set_purity(Purity, ConjInfo3, ConjInfo),
> +        !:Conj = conj(Type, Goals) - ConjInfo
> +    ;
> +        % Not a conjunction.
> +        unexpected(this_file, "recompute_conj_info")
> +    ).
> +
> +    % Update the else part of the new if_then_else goal introduced by the
> +    % transformation as showed in the example. It decrements the value of

s/showed/shown/

> +    % Granularity and uses the decremented value as the last argument of the
> +    % recursive calls.

That comment doesn't make sense.

> +:- pred apply_dg_to_else(hlds_goal::in, hlds_goal::out, prog_var::in,
> +    pred_id::in, proc_id::in, module_info::in, pred_or_func::in,
> +    proc_info::in, proc_info::out) is det.
> +
> +apply_dg_to_else(!Goal, GranularityVar, CallerPredId, CallerProcId,
> +        ModuleInfo, PredOrFunc, !ProcInfo) :-
> +    !.Goal = GoalExpr0 - GoalInfo,
> +    apply_dg_to_else2(GoalExpr0, GoalExpr, 1, _, GranularityVar, 
> CallerPredId,
> +        CallerProcId, ModuleInfo, PredOrFunc, !ProcInfo),
> +    Goal0 = GoalExpr - GoalInfo,
> +    recompute_conj_info(Goal0, !:Goal).
> +
> +:- pred apply_dg_to_else2(hlds_goal_expr::in, hlds_goal_expr::out,
> +    int::in, int::out, prog_var::in, pred_id::in, proc_id::in,
> +    module_info::in, pred_or_func::in, proc_info::in, proc_info::out) is 
> det.
> +
> +apply_dg_to_else2(!GoalExpr, !IndexInConj, GranularityVar, CallerPredId,
> +        CallerProcId, ModuleInfo, PredOrFunc, !ProcInfo) :-
> +    ( !.GoalExpr = conj(plain_conj, Goals0) ->
> +        list.length(Goals0, Length),
> +        ( !.IndexInConj > Length ->
> +            true
> +        ;
> +            list.index1_det(Goals0, !.IndexInConj, Goal0),
> +            Goal0 = GoalExpr0 - GoalInfo0,
> +            ( GoalExpr0 = plain_call(CalleePredId, CalleeProcId, CallArgs0,
> +                CallBuiltin, CallUnifyContext, CallSymName)
> +            ->
> +                ( CalleePredId = CallerPredId, CalleeProcId = CallerProcId 
> ->
> +                    % That is a recursive plain call.
> +
> +                    % Create an int variable containing the value 1.
>
> +                    proc_info_create_var_from_type(int_type, no,
> +                        Var, !ProcInfo),
> +                    make_int_const_construction(Var, 1, UnifyGoal),
> +
> +                    % Create int variable which will contain the result of 
> the
> +                    % decrementation.

I suggest:

 	Create a variable that will contain the decremented
 	granularity distance.

...

> +    % Apply the distance granularity transformation to a disjunction.
> +    %
> +:- pred apply_dg_to_disj(list(hlds_goal)::in,
> +    list(hlds_goal)::in, list(hlds_goal)::out, pred_id::in, proc_id::in,
> +    pred_id::in, sym_name::in, proc_info::in, proc_info::out,
> +    module_info::in, module_info::out, int::in, pred_or_func::in,
> +    maybe(prog_var)::in, maybe(prog_var)::out) is det.
> +
> +apply_dg_to_disj([], !GoalsAcc, _CallerPredId, _CallerProcId,
> +        _PredIdSpecialized, _SymNameSpecialized, !ProcInfo, !ModuleInfo,
> +        _Distance, _PredOrFunc, !MaybeGranularityVar).
> +apply_dg_to_disj([Goal0 | Goals], !GoalsAcc, CallerPredId, CallerProcId,
> +        PredIdSpecialized, SymNameSpecialized, !ProcInfo, !ModuleInfo,
> +        Distance, PredOrFunc, !MaybeGranularityVar) :-
> +    apply_dg_to_goal(Goal0, Goal, CallerPredId, CallerProcId, 
> PredIdSpecialized,
> +        SymNameSpecialized, !ProcInfo, !ModuleInfo, Distance, PredOrFunc, 
> no,
> +        !MaybeGranularityVar, _),
> +    list.append( !.GoalsAcc, [Goal], !:GoalsAcc),
> +    apply_dg_to_disj(Goals, !GoalsAcc, CallerPredId, CallerProcId,
> +        PredIdSpecialized, SymNameSpecialized, !ProcInfo, !ModuleInfo, 
> Distance,
> +        PredOrFunc, !MaybeGranularityVar).
> +
> +    % Apply the distance granularity transformation to a switch.
> +    %
> +:- pred apply_dg_to_switch(
> +    list(case)::in, list(case)::in, list(case)::out, pred_id::in,
> +    proc_id::in, pred_id::in, sym_name::in, proc_info::in, proc_info::out,
> +    module_info::in, module_info::out, int::in, pred_or_func::in,
> +    maybe(prog_var)::in, maybe(prog_var)::out) is det.
> +
> +apply_dg_to_switch([], !CasesAcc, _CallerPredId, _CallerProcId,
> +        _PredIdSpecialized, _SymNameSpecialized, !ProcInfo, !ModuleInfo,
> +        _Distance, _PredOrFunc, !MaybeGranularityVar).
> +apply_dg_to_switch([Case | Cases], !CasesAcc, CallerPredId, CallerProcId,
> +        PredIdSpecialized, SymNameSpecialized, !ProcInfo, !ModuleInfo,
> +        Distance, PredOrFunc, !MaybeGranularityVar) :-
> +    Case = case(Functor, Goal0),
> +    apply_dg_to_goal(Goal0, Goal, CallerPredId, CallerProcId, 
> PredIdSpecialized,
> +        SymNameSpecialized, !ProcInfo, !ModuleInfo, Distance, PredOrFunc, 
> no,
> +        !MaybeGranularityVar, _),
> +    !:CasesAcc = [case(Functor, Goal) | !.CasesAcc],
> +    apply_dg_to_switch(Cases, !CasesAcc, CallerPredId, CallerProcId,
> +        PredIdSpecialized, SymNameSpecialized, !ProcInfo, !ModuleInfo, 
> Distance,
> +        PredOrFunc, !MaybeGranularityVar).
> +
> +%-----------------------------------------------------------------------------%
> +
> +    % This section contains predicates which will apply the second part of 
> the

s/which will/that/


> +    % transformation i.e. updating the recursive plain calls in the original
> +    % predicate to call the specialized version of the predicate.
> +
> +
> +    % Update the recursive calls in each procedure in the list so that the
> +    % pred_id called is the one of the specialized procedure.
> +    %
> +:- pred update_original_predicate_procs(pred_id::in, list(proc_id)::in, 
> int::in,
> +    pred_or_func::in, pred_id::in, sym_name::in, pred_info::in, 
> pred_info::out,
> +    module_info::in, module_info::out) is det.
> +
> +update_original_predicate_procs(_PredId, [], _Distance, _PredOrFunc,
> +        _PredIdSpecialized, _SymNameSpecialized, !PredInfo, !ModuleInfo).
> +update_original_predicate_procs(PredId, [ProcId | ProcIds], Distance,
> +        PredOrFunc, PredIdSpecialized, SymNameSpecialized, !PredInfo,
> +        !ModuleInfo) :-
> +    module_info_proc_info(!.ModuleInfo, proc(PredId, ProcId), ProcInfo0),
> +    proc_info_get_goal(ProcInfo0, Body0),
> +    update_original_predicate_goal(Body0, Body, PredId, ProcId,
> +        PredIdSpecialized, SymNameSpecialized, ProcInfo0, ProcInfo1, 
> Distance,
> +        PredOrFunc),
> +    proc_info_set_goal(Body, ProcInfo1, ProcInfo2),
> +    requantify_proc(ProcInfo2, ProcInfo3),
> +    RecomputeAtomic = no,
> +    recompute_instmap_delta_proc(RecomputeAtomic, ProcInfo3,
> +        ProcInfo, !ModuleInfo),
> +    pred_info_set_proc_info(ProcId, ProcInfo, !PredInfo),
> +    update_original_predicate_procs(PredId, ProcIds, Distance, PredOrFunc,
> +        PredIdSpecialized, SymNameSpecialized, !PredInfo, !ModuleInfo).
> +
> +    % Update the recursive calls of a goal so that the pred_id called is the 
> one
> +    % of the specialized procedure.
> +    %
> +:- pred update_original_predicate_goal(hlds_goal::in, hlds_goal::out,
> +    pred_id::in, proc_id::in, pred_id::in, sym_name::in,
> +    proc_info::in, proc_info::out, int::in, pred_or_func::in) is det.
> +
> +update_original_predicate_goal(!Goal, CallerPredId, CallerProcId,
> +        PredIdSpecialized, SymNameSpecialized, !ProcInfo, Distance,
> +        PredOrFunc) :-
> +    !.Goal = GoalExpr0 - GoalInfo,
> +    (
> +        GoalExpr0 = unify(_, _, _, _, _)
> +    ;
> +        GoalExpr0 = plain_call(_, _, _, _, _, _),
> +        update_original_predicate_plain_call(!Goal, CallerPredId, 
> CallerProcId,
> +            PredIdSpecialized, SymNameSpecialized, !ProcInfo, Distance,
> +            PredOrFunc)
> +    ;
> +        GoalExpr0 = call_foreign_proc(_, _, _, _, _, _, _)
> +    ;
> +        GoalExpr0 = generic_call(_, _, _, _)
> +    ;
> +        GoalExpr0 = conj(Type, Goals0),
> +        update_original_predicate_goals(Goals0, [], Goals1, CallerPredId,
> +            CallerProcId, PredIdSpecialized, SymNameSpecialized, !ProcInfo,
> +            Distance, PredOrFunc),
> +        (
> +            Type = plain_conj,
> +            flatten_conj(Goals1, Goals)
> +        ;
> +            Type = parallel_conj,
> +            % No need to flatten parallel conjunctions as the transformation 
> may
> +            % only create plain conjunctions
> +            % (see update_original_predicate_plain_call).
> +            Goals = Goals1
> +        ),
> +        GoalExpr = conj(Type, Goals),
> +        !:Goal = GoalExpr - GoalInfo
> +    ;
> +        GoalExpr0 = disj(Goals0),
> +        update_original_predicate_goals(Goals0, [], Goals, CallerPredId,
> +            CallerProcId, PredIdSpecialized, SymNameSpecialized, !ProcInfo,
> +            Distance, PredOrFunc),
> +        GoalExpr = disj(Goals),
> +        !:Goal = GoalExpr - GoalInfo
> +    ;
> +        GoalExpr0 = switch(Var, CanFail, Cases0),
> +        update_original_predicate_switch(Cases0, [], Cases, CallerPredId,
> +            CallerProcId, PredIdSpecialized, SymNameSpecialized, !ProcInfo,
> +            Distance, PredOrFunc),
> +        GoalExpr = switch(Var, CanFail, Cases),
> +        !:Goal = GoalExpr - GoalInfo
> +    ;
> +        GoalExpr0 = negation(Goal0),
> +        update_original_predicate_goal(Goal0, Goal, CallerPredId, 
> CallerProcId,
> +            PredIdSpecialized, SymNameSpecialized, !ProcInfo, Distance,
> +            PredOrFunc),
> +        GoalExpr = negation(Goal),
> +        !:Goal = GoalExpr - GoalInfo
> +    ;
> +        GoalExpr0 = scope(_, _)

Don't you need to update the goal inside the scope here?

> +    ;
> +        GoalExpr0 = if_then_else(Vars, If0, Then0, Else0),
> +        update_original_predicate_goal(If0, If, CallerPredId, CallerProcId,
> +            PredIdSpecialized, SymNameSpecialized, !ProcInfo, Distance,
> +            PredOrFunc),
> +        update_original_predicate_goal(Then0, Then, CallerPredId, 
> CallerProcId,
> +            PredIdSpecialized, SymNameSpecialized, !ProcInfo, Distance,
> +            PredOrFunc),
> +        update_original_predicate_goal(Else0, Else, CallerPredId, 
> CallerProcId,
> +            PredIdSpecialized, SymNameSpecialized, !ProcInfo, Distance,
> +            PredOrFunc),
> +        GoalExpr = if_then_else(Vars, If, Then, Else),
> +        !:Goal = GoalExpr - GoalInfo
> +    ;
> +        GoalExpr0 = shorthand(_),
> +        % Shorthand is not supposed to occur here.

s/is not/are not/

...

> +    % Update the plain call so that the pred_id called is the one of the
> +    % specialized procedure.
> +    %
> +:- pred update_original_predicate_plain_call(hlds_goal::in, hlds_goal::out,
> +    pred_id::in, proc_id::in, pred_id::in, sym_name::in,
> +    proc_info::in, proc_info::out, int::in, pred_or_func::in) is det.
> +
> +update_original_predicate_plain_call(!Call, CallerPredId, CallerProcId,
> +        PredIdSpecialized, SymNameSpecialized, !ProcInfo, Distance,
> +        PredOrFunc) :-
> +    !.Call = CallExpr0 - CallInfo0,
> +    ( CallExpr0 = plain_call(CalleePredId, CalleeProcId, CallArgs0,
> +            CallBuiltin, CallUnifyContext, _) ->
> +        ( CalleePredId = CallerPredId, CalleeProcId = CallerProcId ->
> +            % That is a recursive plain call.
> +
> +            % Create the int variable which will be used as the last 
> argument of
> +            % the call for a predicate and as the second last argument for a
> +            % function.
> +            proc_info_create_var_from_type(int_type, no, Var, !ProcInfo),
> +            make_int_const_construction(Var, Distance, UnifyGoal),
> +            (
> +                PredOrFunc = predicate,
> +                % Use the decremented value of GranularityVar as the
> +                % last argument of the call.
> +                list.append(CallArgs0, [Var], CallArgs)
> +            ;
> +                PredOrFunc = function,
> +                % Use the decremented value of GranularityVar as the
> +                % second last argument of the call.
> +                list.length(CallArgs0, LengthCallArgs),
> +                list.det_split_list(LengthCallArgs - 1, CallArgs0,
> +                    StartCallArgs0, EndCallArgs),
> +                list.append(StartCallArgs0, [Var], StartCallArgs),
> +                list.append(StartCallArgs, EndCallArgs, CallArgs)
> +            ),
> +
> +            % Update the pred_id to the pred_id of the cloned pred.
> +            CallExpr = plain_call(PredIdSpecialized, CalleeProcId, CallArgs,
> +                CallBuiltin, CallUnifyContext, SymNameSpecialized),
> +
> +            % Update the nonlocals and the instmap_delta of the 
> hlds_goal_info
> +            % of the recursive plain call for Var.
> +            goal_info_get_nonlocals(CallInfo0, NonLocals0),
> +            set.insert(NonLocals0, Var, NonLocals),
> +            goal_info_set_nonlocals(NonLocals, CallInfo0, CallInfo1),
> +            goal_info_get_instmap_delta(CallInfo1, InstMapDelta0),
> +            MerInst = ground(shared, none),
> +            instmap_delta_insert(Var, MerInst, InstMapDelta0, InstMapDelta),
> +            goal_info_set_instmap_delta(InstMapDelta, CallInfo1, CallInfo),
> +            Call = CallExpr - CallInfo,
> +
> +            % That might unflatten the parent conjunction. We deal with that
> +            % after the conjunction has been processed
> +            % (see update_original_predicate_goal).

I suggest:

 	The resuling conjunction may not be flat.  We deal with that ...

> +            create_conj(UnifyGoal, Call, plain_conj, !:Call)
> +        ;
> +            true
> +        )
> +    ;
> +        % Not a plain call.
> +        unexpected(this_file, "update_original_predicate_plain_call")
> +    ).
> +
> +    % Update the recursive calls of each goal in the list so that the 
> pred_id
> +    % called is the one of the specialized procedure.
> +    %
> +:- pred update_original_predicate_goals(list(hlds_goal)::in,
> +    list(hlds_goal)::in, list(hlds_goal)::out, pred_id::in, proc_id::in,
> +    pred_id::in, sym_name::in, proc_info::in, proc_info::out, int::in,
> +    pred_or_func::in) is det.
> +
> +update_original_predicate_goals([], !GoalsAcc, _CallerPredId,
> +        _CallerProcId, _PredIdSpecialized, _SymNameSpecialized, !ProcInfo,
> +        _Distance, _PredOrFunc).
> +update_original_predicate_goals([Goal0 | Goals], !GoalsAcc, CallerPredId,
> +        CallerProcId, PredIdSpecialized, SymNameSpecialized, !ProcInfo,
> +        Distance, PredOrFunc) :-
> +    update_original_predicate_goal(Goal0, Goal, CallerPredId, CallerProcId,
> +        PredIdSpecialized, SymNameSpecialized, !ProcInfo, Distance, 
> PredOrFunc),
> +    list.append(!.GoalsAcc, [Goal], !:GoalsAcc),
> +    update_original_predicate_goals(Goals, !GoalsAcc, CallerPredId,
> +        CallerProcId, PredIdSpecialized, SymNameSpecialized, !ProcInfo,
> +        Distance, PredOrFunc).
> +
> +    % Update the recursive calls of a switch so that the pred_id called is 
> the
> +    % one of the specialized procedure.
> +    %
> +:- pred update_original_predicate_switch(
> +    list(case)::in, list(case)::in, list(case)::out, pred_id::in,
> +    proc_id::in, pred_id::in, sym_name::in, proc_info::in, proc_info::out,
> +    int::in, pred_or_func::in) is det.
> +
> +update_original_predicate_switch([], !CasesAcc, _CallerPredId, 
> _CallerProcId,
> +        _PredIdSpecialized, _SymNameSpecialized, !ProcInfo, _Distance,
> +        _PredOrFunc).
> +update_original_predicate_switch([Case | Cases], !CasesAcc, CallerPredId,
> +        CallerProcId, PredIdSpecialized, SymNameSpecialized, !ProcInfo,
> +        Distance, PredOrFunc) :-
> +    Case = case(Functor, Goal0),
> +    update_original_predicate_goal(Goal0, Goal, CallerPredId, CallerProcId,
> +        PredIdSpecialized, SymNameSpecialized, !ProcInfo, Distance, 
> PredOrFunc),
> +    !:CasesAcc = [ case(Functor, Goal) | !.CasesAcc ],
> +    update_original_predicate_switch(Cases, !CasesAcc, CallerPredId,
> +        CallerProcId, PredIdSpecialized, SymNameSpecialized, !ProcInfo,
> +        Distance, PredOrFunc).
> +
> +%-----------------------------------------------------------------------------%
> +
> +    % This section contains predicate which are used by the two parts of the
> +    % transformation.

s/the two/both/

> +
> +
> +    % Update the string name of a predicate (same format as make_pred_name 
> in
> +    % prog_util).
> +

Is there a reason why you cannot use make_pred_name to do this?

> +:- pred update_pred_name(string::in, pred_or_func::in, int::in,
> +    string::in, string::out) is det.
> +
> +update_pred_name(Prefix, PredOrFunc, Distance, !PredName) :-
> +    (
> +        PredOrFunc = predicate,
> +        PFS = "pred"
> +    ;
> +        PredOrFunc = function,
> +        PFS = "func"
> +    ),
> +    int_to_string(Distance, PredIdStr),
> +    string.format("%s__%s__%s__%s",
> +        [s(Prefix), s(PFS), s(!.PredName), s(PredIdStr)], !:PredName).
> +
> +:-func granularity_prefix = string.
> +
> +granularity_prefix = "distance_granularity".

That name could potentially clash with user predicates.  I suggest:

 	granularity_prefix = "DistanceGranularityFor".

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