[m-rev.] Re: for review: fix bug in higher order specialization

Ian MacLarty maclarty at csse.unimelb.edu.au
Wed Oct 19 15:56:51 AEDT 2011


I'm committed this now.

On Thu, Oct 13, 2011 at 3:14 PM, Ian MacLarty
<maclarty at csse.unimelb.edu.au> wrote:
> Mark Brown pointed out that my fix excludes specialization opportunities
> where some of the branch arms are unreachable.  For example:
>
> ( ... ->
>    P = f1
> ;
>    throw(...)
> ),
> P(X)
>
> In this case P does not appear in the else part, but it can still
> be specialized to f1 after the if-then-else.
>
> I've fixed this by including the reachability of the branch arm in the
> post_branch_infos and modifying merge_post_branch_infos to include
> all variables in a reachable arm if the other arm is unreachable.
>
> I've also moved the regression test to general, since valid doesn't
> seem to check expected output files.
>
> Here's the revised log message and diff:
>
> Branches: main
>
> Fix a bug in higher order specialization where it incorrectly specialized a
> call to a variable after a branch if the variable was constructed in the branch
> and its value was known in one branch arm, but not the others.
>
> higher_order.m uses a map to track the possible values of higher order
> variables.  The map maps variables to either a constant value, or a
> 'multiple_values' functor to indicate that the variable can contain multiple
> values (and is therefore not specializable).  The problem was there was
> some confusion about what it meant if a variable did not appear in this map.
>
> merge_post_branch_infos was expecting the post_branch_info maps it was merging
> to contain all the higher order variables in the arms, when in fact it only
> contained variables that the goal traversal routines had deemed specializable.
> Any entries it found in one post_branch_info but not the other, would be
> copied to the resulting post_branch_info.  This was incorrect, because if a
> variable did not occur in one post_branch_info its value might simply be
> unknown in that arm (in which case is should not be specializable after
> the branch).
>
> The fix is to remove the multiple_values functor altogether.  A variable now
> only appears in the post_branch_info if its value is known and unique.
> merge_post_branch_infos has been changed so that it drops variables that
> don't appear in both post_branch_infos.
>
> There is one exception to the above where one switch arm is reachable and the
> others are unreachable.  In this case we can copy any variables with unique
> known values in the reachable arm's post_branch_info to the merged
> post_branch_info.  The reachablility of each arm is therefore now also included
> in the post_branch_infos.
>
> compiler/higher_order.m:
>    As above.
>
>    Also remove some comments about the complexity of the
>    merge_post_branch_infos algorithm, as the current algorithm is the obvious
>    one given the new meaning of the post_branch_info maps.
>
> tests/general/Mercury.options:
> tests/general/Mmakefile:
> tests/general/ho_spec_branch_bug.exp:
> tests/general/ho_spec_branch_bug.m:
>    Add a regression test.
>
> Index: compiler/higher_order.m
> ===================================================================
> RCS file: /home/mercury/mercury1/repository/mercury/compiler/higher_order.m,v
> retrieving revision 1.197
> diff -u -r1.197 higher_order.m
> --- compiler/higher_order.m     31 Aug 2011 07:59:32 -0000      1.197
> +++ compiler/higher_order.m     13 Oct 2011 04:09:29 -0000
> @@ -224,7 +224,7 @@
>     --->    higher_order_info(
>                 hoi_global_info         :: higher_order_global_info,
>
> -                % Higher_order variables.
> +                % Higher order variables with unique known values.
>                 hoi_pred_vars           :: pred_vars,
>
>                 % The pred_proc_id, pred_info and proc_info of the procedure
> @@ -307,9 +307,9 @@
>  :- type goal_sizes == map(pred_id, int).
>
>     % Used to hold the value of known higher order variables.
> -    % If a variable is not in the map, it does not have a value yet.
> +    % If a variable is not in the map, it does not have a unique known value.
>     %
> -:- type pred_vars == map(prog_var, maybe_const).
> +:- type pred_vars == map(prog_var, ho_const).
>
>  :- type new_preds == map(pred_proc_id, set(new_pred)).
>
> @@ -319,12 +319,8 @@
>     % must be constants. For pred_consts and type_infos, non-constant
>     % arguments are passed through to any specialised version.
>     %
> -:- type maybe_const
> -    --->    constant(cons_id, list(prog_var))
> -                                    % Unique possible value.
> -
> -    ;       multiple_values.        % Multiple possible values,
> -                                    % cannot specialise.
> +:- type ho_const
> +    --->    constant(cons_id, list(prog_var)).
>
>  :- type ho_params
>     --->    ho_params(
> @@ -586,10 +582,10 @@
>         get_pre_branch_info(!.Info, PreInfo),
>         ho_traverse_goal(Cond0, Cond, !Info),
>         ho_traverse_goal(Then0, Then, !Info),
> -        get_post_branch_info(!.Info, PostThenInfo),
> +        get_post_branch_info_for_goal(!.Info, Then, PostThenInfo),
>         set_pre_branch_info(PreInfo, !Info),
>         ho_traverse_goal(Else0, Else, !Info),
> -        get_post_branch_info(!.Info, PostElseInfo),
> +        get_post_branch_info_for_goal(!.Info, Else, PostElseInfo),
>         merge_post_branch_infos(PostThenInfo, PostElseInfo, PostInfo),
>         set_post_branch_info(PostInfo, !Info),
>         GoalExpr = if_then_else(Vars, Cond, Then, Else),
> @@ -664,7 +660,7 @@
>         !PostInfos, !Info) :-
>     set_pre_branch_info(PreInfo, !Info),
>     ho_traverse_goal(Goal0, Goal, !Info),
> -    get_post_branch_info(!.Info, GoalPostInfo),
> +    get_post_branch_info_for_goal(!.Info, Goal, GoalPostInfo),
>     !:PostInfos = [GoalPostInfo | !.PostInfos],
>     ho_traverse_parallel_conj_2(PreInfo, Goals0, Goals, !PostInfos, !Info).
>
> @@ -699,7 +695,7 @@
>         !PostInfos, !Info) :-
>     set_pre_branch_info(PreInfo, !Info),
>     ho_traverse_goal(Goal0, Goal, !Info),
> -    get_post_branch_info(!.Info, GoalPostInfo),
> +    get_post_branch_info_for_goal(!.Info, Goal, GoalPostInfo),
>     !:PostInfos = [GoalPostInfo | !.PostInfos],
>     ho_traverse_disj_2(PreInfo, Goals0, Goals, !PostInfos, !Info).
>
> @@ -734,15 +730,19 @@
>     Case0 = case(MainConsId, OtherConsIds, Goal0),
>     ho_traverse_goal(Goal0, Goal, !Info),
>     Case = case(MainConsId, OtherConsIds, Goal),
> -    get_post_branch_info(!.Info, GoalPostInfo),
> +    get_post_branch_info_for_goal(!.Info, Goal, GoalPostInfo),
>     !:PostInfos = [GoalPostInfo | !.PostInfos],
>     ho_traverse_cases_2(PreInfo, Cases0, Cases, !PostInfos, !Info).
>
>  :- type pre_branch_info
>     --->    pre_branch_info(pred_vars).
>
> +:- type reachability
> +    --->    reachable
> +    ;       unreachable.
> +
>  :- type post_branch_info
> -    --->    post_branch_info(pred_vars).
> +    --->    post_branch_info(pred_vars, reachability).
>
>  :- pred get_pre_branch_info(higher_order_info::in, pre_branch_info::out)
>     is det.
> @@ -755,24 +755,26 @@
>  set_pre_branch_info(pre_branch_info(PreInfo),
>     Info, Info ^ hoi_pred_vars := PreInfo).
>
> -:- pred get_post_branch_info(higher_order_info::in, post_branch_info::out)
> -    is det.
> +:- pred get_post_branch_info_for_goal(higher_order_info::in, hlds_goal::in,
> +    post_branch_info::out) is det.
>
> -get_post_branch_info(Info, post_branch_info(Info ^ hoi_pred_vars)).
> +get_post_branch_info_for_goal(HOInfo, Goal, PostBranchInfo) :-
> +    InstMapDelta = goal_info_get_instmap_delta(Goal ^ hlds_goal_info),
> +    ( instmap_delta_is_reachable(InstMapDelta) ->
> +        Reachability = reachable
> +    ;
> +        Reachability = unreachable
> +    ),
> +    PostBranchInfo = post_branch_info(HOInfo ^ hoi_pred_vars, Reachability).
>
>  :- pred set_post_branch_info(post_branch_info::in,
>     higher_order_info::in, higher_order_info::out) is det.
>
> -set_post_branch_info(post_branch_info(PostInfo),
> -    Info, Info ^ hoi_pred_vars := PostInfo).
> +set_post_branch_info(post_branch_info(PredVars, _),
> +    Info, Info ^ hoi_pred_vars := PredVars).
>
>     % Merge a bunch of post_branch_infos into one.
>     %
> -    % The algorithm we use has a complexity of N log N, whereas the obvious
> -    % algorithm is quadratic. Since N can be very large for predicates defined
> -    % lots of facts, this can be the difference between being able to compile
> -    % them and having the compiler exhaust available memory in the attempt.
> -    %
>  :- pred merge_post_branch_infos_into_one(list(post_branch_info)::in,
>     post_branch_info::out) is det.
>
> @@ -796,48 +798,53 @@
>
>     % Merge two post_branch_infos.
>     %
> -    % The algorithm we use is designed to minimize worst case complexity,
> -    % to minimize compilation time for predicates defined by clauses in which
> -    % each clause contains lots of variables. This will happen e.g. when the
> -    % clause contains some large ground terms.
> -    %
> -    % We separate out the variables that occur in only one post_branch_info
> -    % to avoid having to process them at all, while allowing the variables
> -    % occur in both post_branch_infos to be processed using a linear algorithm.
> -    % The algorithm here is mostly linear, with an extra log N factor coming in
> -    % from the operations on maps.
> +    % If a variable appears in one post_branch_info, but not the
> +    % other, it is dropped.  Such a variable is either local to
> +    % the branch arm, in which case no subsequent specialization
> +    % opportunities exist, or it does not have a unique constant
> +    % value in one of the branch arms, so we can't specialize it
> +    % outside the branch anyway.  A third possibility is that
> +    % the branch without the variable is unreachable.  In that
> +    % case we include the variable in the result.
>     %
>  :- pred merge_post_branch_infos(post_branch_info::in,
>     post_branch_info::in, post_branch_info::out) is det.
>
>  merge_post_branch_infos(PostA, PostB, Post) :-
> -    PostA = post_branch_info(VarConstMapA),
> -    PostB = post_branch_info(VarConstMapB),
> -    map.keys(VarConstMapA, VarListA),
> -    map.keys(VarConstMapB, VarListB),
> -    set.sorted_list_to_set(VarListA, VarsA),
> -    set.sorted_list_to_set(VarListB, VarsB),
> -    set.intersect(VarsA, VarsB, CommonVars),
> -    VarConstCommonMapA = map.select(VarConstMapA, CommonVars),
> -    VarConstCommonMapB = map.select(VarConstMapB, CommonVars),
> -    map.to_assoc_list(VarConstCommonMapA, VarConstCommonListA),
> -    map.to_assoc_list(VarConstCommonMapB, VarConstCommonListB),
> -    merge_common_var_const_list(VarConstCommonListA, VarConstCommonListB,
> -        [], VarConstCommonList),
> -    set.difference(VarsA, CommonVars, OnlyVarsA),
> -    set.difference(VarsB, CommonVars, OnlyVarsB),
> -    VarConstOnlyMapA = map.select(VarConstMapA, OnlyVarsA),
> -    VarConstOnlyMapB = map.select(VarConstMapB, OnlyVarsB),
> -    map.to_assoc_list(VarConstOnlyMapA, VarConstOnlyListA),
> -    map.to_assoc_list(VarConstOnlyMapB, VarConstOnlyListB),
> -    FinalList = VarConstOnlyListA ++ VarConstOnlyListB ++ VarConstCommonList,
> -    map.from_assoc_list(FinalList, FinalVarConstMap),
> -    Post = post_branch_info(FinalVarConstMap).
> -
> -:- pred merge_common_var_const_list(assoc_list(prog_var, maybe_const)::in,
> -    assoc_list(prog_var, maybe_const)::in,
> -    assoc_list(prog_var, maybe_const)::in,
> -    assoc_list(prog_var, maybe_const)::out) is det.
> +    (
> +        PostA = post_branch_info(VarConstMapA, reachable),
> +        PostB = post_branch_info(VarConstMapB, reachable),
> +        map.keys(VarConstMapA, VarListA),
> +        map.keys(VarConstMapB, VarListB),
> +        set.sorted_list_to_set(VarListA, VarsA),
> +        set.sorted_list_to_set(VarListB, VarsB),
> +        set.intersect(VarsA, VarsB, CommonVars),
> +        VarConstCommonMapA = map.select(VarConstMapA, CommonVars),
> +        VarConstCommonMapB = map.select(VarConstMapB, CommonVars),
> +        map.to_assoc_list(VarConstCommonMapA, VarConstCommonListA),
> +        map.to_assoc_list(VarConstCommonMapB, VarConstCommonListB),
> +        merge_common_var_const_list(VarConstCommonListA, VarConstCommonListB,
> +            [], VarConstCommonList),
> +        map.from_assoc_list(VarConstCommonList, FinalVarConstMap),
> +        Post = post_branch_info(FinalVarConstMap, reachable)
> +    ;
> +        PostA = post_branch_info(_, unreachable),
> +        PostB = post_branch_info(_, reachable),
> +        Post = PostB
> +    ;
> +        PostA = post_branch_info(_, reachable),
> +        PostB = post_branch_info(_, unreachable),
> +        Post = PostA
> +    ;
> +        PostA = post_branch_info(_, unreachable),
> +        PostB = post_branch_info(_, unreachable),
> +        Post = post_branch_info(map.init, unreachable)
> +    ).
> +
> +:- pred merge_common_var_const_list(assoc_list(prog_var, ho_const)::in,
> +    assoc_list(prog_var, ho_const)::in,
> +    assoc_list(prog_var, ho_const)::in,
> +    assoc_list(prog_var, ho_const)::out) is det.
>
>  merge_common_var_const_list([], [], !List).
>  merge_common_var_const_list([], [_ | _], !MergedList) :-
> @@ -848,17 +855,10 @@
>         !MergedList) :-
>     expect(unify(VarA, VarB), $module, $pred, "var mismatch"),
>     ( ValueA = ValueB ->
> -        % It does not matter whether ValueA is bound to constant(_, _)
> -        % or to multiple_values, in both cases, if ValueA = ValueB, the
> -        % right value for Value is ValueA.
> -        Value = ValueA
> -    ;
> -        % Either ValueA and ValueB are both bound to different constants,
> -        % or one is constant and the other is multiple_values. In both cases,
> -        % the right value for Value is multiple_values.
> -        Value = multiple_values
> +        !:MergedList = [VarA - ValueA | !.MergedList]
> +    ;
> +        !:MergedList = !.MergedList
>     ),
> -    !:MergedList = [VarA - Value | !.MergedList],
>     merge_common_var_const_list(ListA, ListB, !MergedList).
>
>  :- pred check_unify(unification::in,
> @@ -881,18 +881,9 @@
>         (
>             IsInteresting = yes,
>             PredVars0 = !.Info ^ hoi_pred_vars,
> -            ( map.search(PredVars0, LVar, Specializable) ->
> -                (
> -                    % We cannot specialize calls involving a variable with
> -                    % more than one possible value.
> -                    Specializable = constant(_, _),
> -                    map.det_update(LVar, multiple_values, PredVars0, PredVars),
> -                    !Info ^ hoi_pred_vars := PredVars
> -                ;
> -                    % If a variable is already non-specializable, it can't
> -                    % become specializable.
> -                    Specializable = multiple_values
> -                )
> +            ( map.search(PredVars0, LVar, _) ->
> +                % A variable cannot be constructed twice.
> +                unexpected($module, $pred, "variable constructed twice")
>             ;
>                 map.det_insert(LVar, constant(ConsId, Args),
>                     PredVars0, PredVars),
> Index: tests/general/Mercury.options
> ===================================================================
> RCS file: /home/mercury/mercury1/repository/tests/general/Mercury.options,v
> retrieving revision 1.5
> diff -u -r1.5 Mercury.options
> --- tests/general/Mercury.options       15 Jun 2011 01:05:34 -0000      1.5
> +++ tests/general/Mercury.options       13 Oct 2011 04:09:31 -0000
> @@ -4,6 +4,8 @@
>  MCFLAGS-mode_inf_bug = --infer-all
>  MCFLAGS-mode_inference_reorder = --infer-all
>
> +MCFLAGS-ho_spec_branch_bug = --optimize-higher-order
> +
>  # The intermod_type test is a regression test for a bug that occurred only
>  # when intermodule optimization was enabled.
>  MCFLAGS-intermod_type = --intermodule-optimization
> Index: tests/general/Mmakefile
> ===================================================================
> RCS file: /home/mercury/mercury1/repository/tests/general/Mmakefile,v
> retrieving revision 1.61
> diff -u -r1.61 Mmakefile
> --- tests/general/Mmakefile     7 Mar 2011 11:30:09 -0000       1.61
> +++ tests/general/Mmakefile     13 Oct 2011 04:09:31 -0000
> @@ -30,6 +30,7 @@
>                hello_again \
>                higher_order \
>                hlc_name_mangling \
> +               ho_spec_branch_bug \
>                intermod_type \
>                interpreter \
>                io_foldl \
> Index: tests/general/ho_spec_branch_bug.exp
> ===================================================================
> RCS file: tests/general/ho_spec_branch_bug.exp
> diff -N tests/general/ho_spec_branch_bug.exp
> --- /dev/null   1 Jan 1970 00:00:00 -0000
> +++ tests/general/ho_spec_branch_bug.exp        13 Oct 2011 04:09:31 -0000
> @@ -0,0 +1 @@
> +ho2
> Index: tests/general/ho_spec_branch_bug.m
> ===================================================================
> RCS file: tests/general/ho_spec_branch_bug.m
> diff -N tests/general/ho_spec_branch_bug.m
> --- /dev/null   1 Jan 1970 00:00:00 -0000
> +++ tests/general/ho_spec_branch_bug.m  13 Oct 2011 04:09:31 -0000
> @@ -0,0 +1,41 @@
> +% Regression test for a bug where the compiler would incorrectly specialize
> +% the call to P in do_stuff.
> +:- module ho_spec_branch_bug.
> +
> +:- interface.
> +
> +:- import_module io.
> +
> +:- pred main(io::di, io::uo) is det.
> +
> +:- implementation.
> +
> +:- import_module maybe.
> +
> +main(!IO) :-
> +    do_stuff(yes(1), !IO).
> +
> +:- pred ho1(io::di, io::uo) is det.
> +
> +ho1(!IO) :- io.write_string("ho1\n", !IO).
> +
> +:- pred ho2(io::di, io::uo) is det.
> +
> +ho2(!IO) :- io.write_string("ho2\n", !IO).
> +
> +:- func get_ho2 = (pred(io, io)).
> +:- mode get_ho2 = out(pred(di, uo) is det) is det.
> +
> +get_ho2 = ho2.
> +
> +:- pred do_stuff(maybe(int)::in, io::di, io::uo) is det.
> +
> +do_stuff(Maybe, !IO) :-
> +    (
> +        Maybe = no,
> +        P = ho1
> +    ;
> +        Maybe = yes(_),
> +        P = get_ho2
> +    ),
> +    P(!IO).
>

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