[m-rev.] for review: more speeds in inst handling

Peter Wang novalazy at gmail.com
Thu Mar 5 17:38:07 AEDT 2015


On Wed, 04 Mar 2015 01:43:53 +1100 (EST), "Zoltan Somogyi" <zoltan.somogyi at runbox.com> wrote:
> For review by anyone.
> 
> More speedups of inst handling code.
> 
> On tools/speedtest -l -m, my tests show a speedup of about 2%, but 
> on Dirk's stress test module, for which the compiler (used to) spend
> almost all its time handling insts, the speedup is about 40%.
> 
> This diff also contains some small incidental changes I stumbled upon
> the "need" for while working on the main change.
> 
...

inst_match.m was not described.


> diff --git a/compiler/hlds_data.m b/compiler/hlds_data.m
> index 45fa7e5..1ed74e7 100644
> --- a/compiler/hlds_data.m
> +++ b/compiler/hlds_data.m
> @@ -730,6 +731,13 @@ cons_table_optimize(!ConsTable) :-
>                  mer_type              % Argument type.
>              ).
>  
> +    % A type_ctor essentially contains three components. The raw name
> +    % of the type constructor, its module qualification, and its arity.
> +    % I (zs) tried replacing this table with a two-stage map (from raw name
> +    % to a subtable that itself mapped the full type_ctor to no_tag_type,
> +    % in an attempt to make the main part of the looked use cheaper
> +    % comparisons, on just raw strings. However, this change effectively
> +    % lead to no change in performance.

led

> @@ -1115,6 +1193,287 @@ set_type_defn_in_exported_eqv(InExportedEqv, !Defn) :-
>  
>  :- implementation.
>  
> +%---------------------------------------------------------------------------%
> +%
> +% I (zs) have tried making the merge_inst_table a two-stage table,
> +% i.e. being map(mer_inst, map(mer_inst, maybe_inst)), in the hope
> +% of making lookups faster, but it lead to a slowdown, not a speedup.

led

> +
> +det_update_ground_inst(GroundInstInfo, MaybeInstDet, !GroundnstTable) :-
> +    map.det_update(GroundInstInfo, MaybeInstDet, !GroundnstTable).

GroundInstTable

> +%---------------------------------------------------------------------------%
> +
> +unify_insts_to_sorted_pairs(UnifyInstTable, AssocList) :-
> +    UnifyInstTable = unify_inst_table(LiveRealTable, LiveFakeTable,
> +        DeadRealTable, DeadFakeTable),
> +    map.to_assoc_list(LiveRealTable, LiveRealPairInsts),
> +    map.to_assoc_list(LiveFakeTable, LiveFakePairInsts),
> +    map.to_assoc_list(DeadRealTable, DeadRealPairInsts),
> +    map.to_assoc_list(DeadFakeTable, DeadFakePairInsts),
> +    some [!RevAssocList] (
> +        !:RevAssocList = [],
> +        accumulate_unify_insts(is_live, real_unify, LiveRealPairInsts,
> +            !RevAssocList),
> +        accumulate_unify_insts(is_live, fake_unify, LiveFakePairInsts,
> +            !RevAssocList),
> +        accumulate_unify_insts(is_dead, real_unify, DeadRealPairInsts,
> +            !RevAssocList),
> +        accumulate_unify_insts(is_dead, fake_unify, DeadFakePairInsts,
> +            !RevAssocList),
> +        list.reverse(!.RevAssocList, AssocList)
> +    ).
...
> +%---------------------------------------------------------------------------%
> +
> +unify_insts_from_sorted_pairs(AssocList0, UnifyInstTable) :-
> +    unify_inst_subtable_from_sorted_pairs(is_live, real_unify,
> +        AssocList0, AssocList1, [], RevLiveRealAssocList),
> +    unify_inst_subtable_from_sorted_pairs(is_live, fake_unify,
> +        AssocList1, AssocList2, [], RevLiveFakeAssocList),
> +    unify_inst_subtable_from_sorted_pairs(is_dead, real_unify,
> +        AssocList2, AssocList3, [], RevDeadRealAssocList),
> +    unify_inst_subtable_from_sorted_pairs(is_dead, fake_unify,
> +        AssocList3, AssocList4, [], RevDeadFakeAssocList),

Maybe mention that the order corresponds to unify_insts_to_sorted_pairs.

> diff --git a/compiler/hlds_out_mode.m b/compiler/hlds_out_mode.m
> index fb8cd81..a4f03dd 100644
> --- a/compiler/hlds_out_mode.m
> +++ b/compiler/hlds_out_mode.m
> @@ -305,24 +310,47 @@ inst_result_contains_any_to_term(Context, ContainsAny) = Term :-
...
>  
> +:- func inst_result_contains_inst_vars_to_term(prog_context,
> +    inst_result_contains_inst_vars) = prog_term.
> +
> +inst_result_contains_inst_vars_to_term(Context, ContainsInstVars) = Term :-
> +    (
> +        ContainsInstVars = inst_result_contains_inst_vars_unknown,
> +        Term = term.functor(term.atom("contains_inst_vars_unknown"),
> +            [], Context)
> +    ;
> +        ContainsInstVars = inst_result_contains_inst_vars_known(InstVarSet),
> +        set.to_sorted_list(InstVarSet, InstVars),
> +        InstVarTerms = list.map(inst_var_to_term(Context), InstVars),
> +        Term = term.functor(term.atom("contains_types_known"),
> +            InstVarTerms, Context)
> +    ).

contains_inst_vars_known

> diff --git a/compiler/inst_match.m b/compiler/inst_match.m
> index 8c551cc..aac9948 100644
> --- a/compiler/inst_match.m
> +++ b/compiler/inst_match.m
> @@ -2118,24 +2135,20 @@ bound_inst_list_is_ground_mt([BoundInst | BoundInsts], MaybeType,
>      inst_list_is_ground_mt(Args, MaybeTypes, ModuleInfo),
>      bound_inst_list_is_ground_mt(BoundInsts, MaybeType, ModuleInfo).
>  
> -:- pred inst_results_bound_inst_list_is_ground_or_any(inst_test_results::in,
> -    list(bound_inst)::in, module_info::in) is semidet.
> -
>  inst_results_bound_inst_list_is_ground_or_any(InstResults, BoundInsts,
>          ModuleInfo) :-
>      require_complete_switch [InstResults]
>      (
>          InstResults = inst_test_results_fgtc
>      ;
> -        InstResults = inst_test_results(GroundnessResult, _, _, _),
> +        InstResults = inst_test_results(GroundnessResult, _, _, _, _, _),
>          require_complete_switch [GroundnessResult]
>          (
>              GroundnessResult = inst_result_is_ground
>          ;
> -            GroundnessResult = inst_result_is_not_ground,
> -            fail
> -        ;
> -            GroundnessResult = inst_result_groundness_unknown,
> +            ( GroundnessResult = inst_result_is_not_ground
> +            ; GroundnessResult = inst_result_groundness_unknown
> +            ),
>              bound_inst_list_is_ground_or_any(BoundInsts, ModuleInfo)
>          )
>      ;

Describe this change in the log.

> diff --git a/compiler/inst_user.m b/compiler/inst_user.m
> index 2eff802..3b66390 100644
> --- a/compiler/inst_user.m
> +++ b/compiler/inst_user.m
> @@ -190,15 +207,19 @@ pretest_inst(Inst0, Inst, UserInstTable0, Groundness, ContainsAny,
>      ;
>          Inst0 = constrained_inst_vars(InstVars, SubInst0),
>          pretest_inst(SubInst0, SubInst, UserInstTable0,
> -            Groundness, ContainsAny, ContainsInstNames, ContainsTypes,
> -            !MaybeInstDefnsMap),
> +            Groundness, ContainsAny, ContainsInstNames, ContainsInstVars0,
> +            ContainsTypes, !MaybeInstDefnsMap),
> +        combine_contains_inst_vars_results(
> +            inst_result_contains_inst_vars_known(InstVars),
> +            ContainsInstVars0, ContainsInstVars),
>          Inst = constrained_inst_vars(InstVars, SubInst)
>      ;
>          Inst0 = defined_inst(_InstName),
>          % ZZZ
>          Groundness = inst_result_groundness_unknown,
>          ContainsAny = inst_result_contains_any_unknown,
> -        ContainsInstNames = inst_result_contains_instnames_unknown,
> +        ContainsInstNames = inst_result_contains_inst_names_unknown,
> +        ContainsInstVars = inst_result_contains_inst_vars_known(set.init),

inst_result_contains_inst_vars_unknown?

> diff --git a/compiler/mode_util.m b/compiler/mode_util.m
> index a56c1a8..3fcb23b 100644
> --- a/compiler/mode_util.m
> +++ b/compiler/mode_util.m
...
> +    % The code here would be slightly cleaner if ConstructNewInst's type
> +    % was maybe(list(bound_inst)), since we wouldn't have to set BoundInsts
> +    % and PropagatedResult if ConstructNewInst = no, but this predicate
> +    % is a performance bottleneck, so we want to minimize our memory
> +    % allocations.
> +    (
> +        ConstructNewInst = no,
> +        Inst = Inst0
> +    ;
> +        ConstructNewInst = yes,
> +        (
> +            BoundInsts = [],
> +            Inst = not_reached
> +        ;
> +            BoundInsts = [_ | _],
> +            (
> +                InstResults0 = inst_test_results_fgtc,
> +                InstResults = InstResults0
> +            ;
> +                InstResults0 = inst_test_no_results,
> +                InstResults = inst_test_results(inst_result_groundness_unknown,
> +                    inst_result_contains_any_unknown,
> +                    inst_result_contains_inst_names_unknown,
> +                    inst_result_contains_inst_vars_unknown,
> +                    inst_result_contains_types_unknown, PropagatedResult)
> +            ;
> +                InstResults0 = inst_test_results(GroundNessResult0,
> +                    ContainsAnyResult, _, _, _, _),
> +                % XXX I (zs) don't understand propagate_ctor_info_3 well enough
> +                % to figure out under what circumstances we could keep
> +                % the parts of InstResult0 we are clobbering here.

propagate_ctor_info_3 was renamed to
propagate_ctor_info_into_bound_functors.

> diff --git a/compiler/prog_data.m b/compiler/prog_data.m
> index 137c3d4..ae4c8af 100644
> --- a/compiler/prog_data.m
> +++ b/compiler/prog_data.m
...
>  :- type inst_result_contains_types
>      --->    inst_result_contains_types_known(set(type_ctor))
>              % All the type_ctors inside typed_inst nodes of the the inst
> -            % are given in the set. This gives a guarantee analogous to
> -            % inst_result_contains_instnames_known.
> +            % are given in the set. This is not guarantee that all the
> +            % type_ctors  in the set appear in the inst, but it is a guarantee
> +            % that a type_ctor that appears in the inst will appear in the set.
>      ;       inst_result_contains_types_unknown.
>  

Double space.

Peter



More information about the reviews mailing list