Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:23
erlang
4421-Eliminate-redundant-branches.patch
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 4421-Eliminate-redundant-branches.patch of Package erlang
From 3e4b86a954a24aed31f1bc17d22a1f4e1e05e8aa Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org> Date: Mon, 28 Jun 2021 15:23:22 +0200 Subject: [PATCH 1/7] Eliminate redundant branches `sys_core_fold` has a weak optimization that rewrites: case BoolExpr of true -> true false -> false end to simply: BoolExpr That optimization is weak because it will only handle a boolean expression in a Core Erlang `case` expression, not other boolean expressions resulting from, for example, guards. Implement the optimization in a more effective way in the `beam_ssa_opt` pass. --- lib/compiler/src/beam_ssa_opt.erl | 124 ++++++++++++++++++++++++++- lib/compiler/src/sys_core_fold.erl | 47 +++------- lib/compiler/test/beam_ssa_SUITE.erl | 16 +++- 3 files changed, 149 insertions(+), 38 deletions(-) diff --git a/lib/compiler/src/beam_ssa_opt.erl b/lib/compiler/src/beam_ssa_opt.erl index 3ffa8ecc0a..72e320749e 100644 --- a/lib/compiler/src/beam_ssa_opt.erl +++ b/lib/compiler/src/beam_ssa_opt.erl @@ -39,7 +39,7 @@ -include("beam_ssa_opt.hrl"). --import(lists, [all/2,append/1,duplicate/2,flatten/1,foldl/3, +-import(lists, [all/2,append/1,droplast/1,duplicate/2,flatten/1,foldl/3, keyfind/3,last/1,mapfoldl/3,member/2, partition/2,reverse/1,reverse/2, splitwith/2,sort/1,takewhile/2,unzip/1]). @@ -301,6 +301,7 @@ epilogue_passes(Opts) -> ?PASS(ssa_opt_bsm_shortcut), ?PASS(ssa_opt_sink), ?PASS(ssa_opt_blockify), + ?PASS(ssa_opt_redundant_br), ?PASS(ssa_opt_merge_blocks), ?PASS(ssa_opt_get_tuple_element), ?PASS(ssa_opt_tail_calls), @@ -3101,6 +3102,127 @@ is_tail_call_is([I|Is], Bool, Ret, Acc) -> is_tail_call_is(Is, Bool, Ret, [I|Acc]); is_tail_call_is([], _Bool, _Ret, _Acc) -> no. +%%% +%%% Eliminate redundant branches. +%%% +%%% Redundant `br` instructions following calls to guard BIFs such as: +%%% +%%% @bif_result = bif:Bif ... +%%% br @bif_result, ^100, ^200 +%%% +%%% 100: +%%% ret `true` +%%% +%%% 200: +%%% ret `false` +%%% +%%% can can be rewritten to: +%%% +%%% @bif_result = bif:Bif ... +%%% ret @bif_result +%%% +%%% A similar rewriting is possible if the true and false branches end +%%% up at a phi node. +%%% +%%% A code sequence such as: +%%% +%%% @ssa_bool = bif:'=:=' Var, Other +%%% br @ssa_bool, ^100, ^200 +%%% +%%% 100: +%%% ret Other +%%% +%%% 200: +%%% ret Var +%%% +%%% can be rewritten to: +%%% +%%% ret Var +%%% + +ssa_opt_redundant_br({#opt_st{ssa=Blocks0}=St, FuncDb}) -> + Blocks = redundant_br(beam_ssa:rpo(Blocks0), Blocks0), + {St#opt_st{ssa=Blocks}, FuncDb}. + +redundant_br([L|Ls], Blocks0) -> + Blk0 = map_get(L, Blocks0), + case Blk0 of + #b_blk{is=Is, + last=#b_br{bool=#b_var{}=Bool, + succ=Succ, + fail=Fail}} -> + case Blocks0 of + #{Succ := #b_blk{is=[],last=#b_ret{arg=#b_literal{val=true}}}, + Fail := #b_blk{is=[],last=#b_ret{arg=#b_literal{val=false}}}} -> + case redundant_br_safe_bool(Is, Bool) of + true -> + Blk = Blk0#b_blk{last=#b_ret{arg=Bool}}, + Blocks = Blocks0#{L => Blk}, + redundant_br(Ls, Blocks); + false -> + redundant_br(Ls, Blocks0) + end; + #{Succ := #b_blk{is=[],last=#b_br{succ=PhiL,fail=PhiL}}, + Fail := #b_blk{is=[],last=#b_br{succ=PhiL,fail=PhiL}}} -> + case redundant_br_safe_bool(Is, Bool) of + true -> + Blocks = redundant_br_phi(L, Blk0, PhiL, Blocks0), + redundant_br(Ls, Blocks); + false -> + redundant_br(Ls, Blocks0) + end; + #{Succ := #b_blk{is=[],last=#b_ret{arg=Other}}, + Fail := #b_blk{is=[],last=#b_ret{arg=Var}}} when Is =/= [] -> + case last(Is) of + #b_set{op={bif,'=:='},args=[Var,Other]} -> + Blk = Blk0#b_blk{is=droplast(Is), + last=#b_ret{arg=Var}}, + Blocks = Blocks0#{L => Blk}, + redundant_br(Ls, Blocks); + #b_set{} -> + redundant_br(Ls, Blocks0) + end; + #{} -> + redundant_br(Ls, Blocks0) + end; + _ -> + redundant_br(Ls, Blocks0) + end; +redundant_br([], Blocks) -> Blocks. + +redundant_br_phi(L, Blk0, PhiL, Blocks) -> + #b_blk{is=Is0} = PhiBlk0 = map_get(PhiL, Blocks), + case Is0 of + [#b_set{op=phi},#b_set{op=phi}|_] -> + Blocks; + [#b_set{op=phi,args=PhiArgs0}=I0|Is] -> + #b_blk{last=#b_br{succ=Succ,fail=Fail}} = Blk0, + BoolPhiArgs = [{#b_literal{val=false},Fail}, + {#b_literal{val=true},Succ}], + PhiArgs1 = ordsets:from_list(PhiArgs0), + case ordsets:is_subset(BoolPhiArgs, PhiArgs1) of + true -> + #b_blk{last=#b_br{bool=Bool}} = Blk0, + PhiArgs = ordsets:add_element({Bool,L}, PhiArgs1), + I = I0#b_set{args=PhiArgs}, + PhiBlk = PhiBlk0#b_blk{is=[I|Is]}, + Br = #b_br{bool=#b_literal{val=true},succ=PhiL,fail=PhiL}, + Blk = Blk0#b_blk{last=Br}, + Blocks#{L := Blk, PhiL := PhiBlk}; + false -> + Blocks + end + end. + +redundant_br_safe_bool([], _Bool) -> + true; +redundant_br_safe_bool(Is, Bool) -> + case last(Is) of + #b_set{op={bif,_}} -> true; + #b_set{op=has_map_field} -> true; + #b_set{dst=Dst} -> Dst =/= Bool + end. + %%% %%% Common utilities. %%% diff --git a/lib/compiler/src/sys_core_fold.erl b/lib/compiler/src/sys_core_fold.erl index 01e9987196..3653d5e647 100644 --- a/lib/compiler/src/sys_core_fold.erl +++ b/lib/compiler/src/sys_core_fold.erl @@ -324,19 +324,16 @@ expr(#c_case{}=Case0, Ctxt, Sub) -> %% (in addition to any warnings that may have been emitted %% according to the rules above). %% - case opt_bool_case(Case0, Sub) of - #c_case{anno=Anno,arg=Arg0,clauses=Cs0}=Case1 -> - Arg1 = body(Arg0, value, Sub), - LitExpr = cerl:is_literal(Arg1), - {Arg2,Cs1} = case_opt(Arg1, Cs0, Sub), - Cs2 = clauses(Arg2, Cs1, Ctxt, Sub, LitExpr, Anno), - Case = Case1#c_case{arg=Arg2,clauses=Cs2}, - warn_no_clause_match(Case1, Case), - Expr = eval_case(Case, Sub), - move_case_into_arg(Expr, Sub); - Other -> - expr(Other, Ctxt, Sub) - end; + Case1 = opt_bool_case(Case0, Sub), + #c_case{anno=Anno,arg=Arg0,clauses=Cs0} = Case1, + Arg1 = body(Arg0, value, Sub), + LitExpr = cerl:is_literal(Arg1), + {Arg2,Cs1} = case_opt(Arg1, Cs0, Sub), + Cs2 = clauses(Arg2, Cs1, Ctxt, Sub, LitExpr, Anno), + Case = Case1#c_case{arg=Arg2,clauses=Cs2}, + warn_no_clause_match(Case1, Case), + Expr = eval_case(Case, Sub), + move_case_into_arg(Expr, Sub); expr(#c_apply{anno=Anno,op=Op0,args=As0}=Apply0, _, Sub) -> Op1 = expr(Op0, value, Sub), As1 = expr_list(As0, value, Sub), @@ -1593,34 +1590,12 @@ opt_bool_not(#c_case{arg=Arg,clauses=Cs0}=Case0) -> Case = Case0#c_case{arg=Expr,clauses=Cs}, opt_bool_not(Case); _ -> - opt_bool_case_redundant(Case0) + Case0 end. opt_bool_not_invert(#c_clause{pats=[#c_literal{val=Bool}]}=C) -> C#c_clause{pats=[#c_literal{val=not Bool}]}. -%% opt_bool_case_redundant(Core) -> Core'. -%% If the sole purpose of the case is to verify that the case -%% expression is indeed boolean, we do not need the case -%% (since we have already verified that the case expression is -%% boolean). -%% -%% case BoolExpr of -%% true -> true ==> BoolExpr -%% false -> false -%% end. -%% -opt_bool_case_redundant(#c_case{arg=Arg,clauses=Cs}=Case) -> - case all(fun opt_bool_case_redundant_1/1, Cs) of - true -> Arg; - false -> Case - end. - -opt_bool_case_redundant_1(#c_clause{pats=[#c_literal{val=B}], - body=#c_literal{val=B}}) -> - true; -opt_bool_case_redundant_1(_) -> false. - %% eval_case(Case) -> #c_case{} | #c_let{}. %% If possible, evaluate a case at compile time. We know that the %% last clause is guaranteed to match so if there is only one clause diff --git a/lib/compiler/test/beam_ssa_SUITE.erl b/lib/compiler/test/beam_ssa_SUITE.erl index 590ee231ff..6bada57a2a 100644 --- a/lib/compiler/test/beam_ssa_SUITE.erl +++ b/lib/compiler/test/beam_ssa_SUITE.erl @@ -25,7 +25,8 @@ cover_ssa_dead/1,combine_sw/1,share_opt/1, beam_ssa_dead_crash/1,stack_init/1, mapfoldl/0,mapfoldl/1, - grab_bag/1,coverage/1]). + grab_bag/1,redundant_br/1, + coverage/1]). suite() -> [{ct_hooks,[ts_install_cth]}]. @@ -45,6 +46,7 @@ groups() -> beam_ssa_dead_crash, stack_init, grab_bag, + redundant_br, coverage ]}]. @@ -1084,6 +1086,18 @@ grab_bag_17() -> [] end. +redundant_br(_Config) -> + {false,{x,y,z}} = redundant_br_1(id({x,y,z})), + {true,[[a,b,c]]} = redundant_br_1(id([[[a,b,c]]])), + ok. + +redundant_br_1(Specs0) -> + {Join,Specs} = + if + is_list(hd(hd(Specs0))) -> {true,hd(Specs0)}; + true -> {false,Specs0} + end, + id({Join,Specs}). coverage(_Config) -> -- 2.31.1
Locations
Projects
Search
Status Monitor
Help
OpenBuildService.org
Documentation
API Documentation
Code of Conduct
Contact
Support
@OBShq
Terms
openSUSE Build Service is sponsored by
The Open Build Service is an
openSUSE project
.
Sign Up
Log In
Places
Places
All Projects
Status Monitor