Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:23
erlang
2452-Explicit-pass-RPO-to-beam_ssa-functions-co...
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 2452-Explicit-pass-RPO-to-beam_ssa-functions-cont.patch of Package erlang
From 35f10baeda472d82f568be6802bd4abda8da4195 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= <jose.valim@dashbit.co> Date: Tue, 3 Nov 2020 12:21:50 +0100 Subject: [PATCH] Explicit pass RPO to beam_ssa functions (cont) This patch finishes the work started on 0ce3fb91 by explicitly passing RPO to the remaining functions in beam_ssa. This commit avoids the double RPO computation in 5 other occasions. --- lib/compiler/src/beam_ssa.erl | 48 +++++++++++------------ lib/compiler/src/beam_ssa_bool.erl | 4 +- lib/compiler/src/beam_ssa_bsm.erl | 10 +++-- lib/compiler/src/beam_ssa_opt.erl | 6 ++- lib/compiler/src/beam_ssa_pre_codegen.erl | 41 +++++++++++-------- 5 files changed, 59 insertions(+), 50 deletions(-) diff --git a/lib/compiler/src/beam_ssa.erl b/lib/compiler/src/beam_ssa.erl index d5fe4b7d9c..76303b34cb 100644 --- a/lib/compiler/src/beam_ssa.erl +++ b/lib/compiler/src/beam_ssa.erl @@ -23,7 +23,7 @@ -export([add_anno/3,get_anno/2,get_anno/3, between/4, clobbers_xregs/1,def/2,def_unused/3, - definitions/1, + definitions/2, dominators/2,dominators_from_predecessors/2,common_dominators/3, flatmapfold_instrs/4, fold_blocks/4, @@ -32,13 +32,13 @@ linearize/1, mapfold_blocks/4, mapfold_instrs/4, - merge_blocks/1, + merge_blocks/2, normalize/1, no_side_effect/1, predecessors/1, rename_vars/3, rpo/1,rpo/2, - split_blocks/3, + split_blocks/4, successors/1,successors/2, trim_unreachable/1, used/1,uses/2]). @@ -344,8 +344,7 @@ successors(L, Blocks) -> Def :: ordsets:ordset(var_name()). def(Ls, Blocks) -> - Top = rpo(Ls, Blocks), - Blks = [map_get(L, Blocks) || L <- Top], + Blks = [map_get(L, Blocks) || L <- Ls], def_1(Blks, []). -spec def_unused(Ls, Used, Blocks) -> {Def,Unused} when @@ -356,9 +355,8 @@ def(Ls, Blocks) -> Unused :: ordsets:ordset(var_name()). def_unused(Ls, Unused, Blocks) -> - Top = rpo(Ls, Blocks), - Blks = [map_get(L, Blocks) || L <- Top], - Preds = cerl_sets:from_list(Top), + Blks = [map_get(L, Blocks) || L <- Ls], + Preds = cerl_sets:from_list(Ls), def_unused_1(Blks, Preds, [], Unused). %% dominators(Labels, BlockMap) -> {Dominators,Numbering}. @@ -533,11 +531,10 @@ between(From, To, Preds, Blocks) -> -spec rename_vars(Rename, [label()], block_map()) -> block_map() when Rename :: rename_map() | rename_proplist(). -rename_vars(Rename, From, Blocks) when is_list(Rename) -> - rename_vars(maps:from_list(Rename), From, Blocks); -rename_vars(Rename, From, Blocks) when is_map(Rename)-> - Top = rpo(From, Blocks), - Preds = cerl_sets:from_list(Top), +rename_vars(Rename, Labels, Blocks) when is_list(Rename) -> + rename_vars(maps:from_list(Rename), Labels, Blocks); +rename_vars(Rename, Labels, Blocks) when is_map(Rename)-> + Preds = cerl_sets:from_list(Labels), F = fun(#b_set{op=phi,args=Args0}=Set) -> Args = rename_phi_vars(Args0, Preds, Rename), normalize(Set#b_set{args=Args}); @@ -551,23 +548,23 @@ rename_vars(Rename, From, Blocks) when is_map(Rename)-> (#b_ret{arg=Arg}=Ret) -> normalize(Ret#b_ret{arg=rename_var(Arg, Rename)}) end, - map_instrs_1(Top, F, Blocks). + map_instrs_1(Labels, F, Blocks). %% split_blocks(Predicate, Blocks0, Count0) -> {Blocks,Count}. %% Call Predicate(Instruction) for each instruction in all %% blocks. If Predicate/1 returns true, split the block %% before this instruction. --spec split_blocks(Pred, Blocks0, Count0) -> {Blocks,Count} when +-spec split_blocks(Labels, Pred, Blocks0, Count0) -> {Blocks,Count} when + Labels :: [label()], Pred :: fun((b_set()) -> boolean()), Blocks :: block_map(), - Count0 :: beam_ssa:label(), + Count0 :: label(), Blocks0 :: block_map(), Blocks :: block_map(), - Count :: beam_ssa:label(). + Count :: label(). -split_blocks(P, Blocks, Count) -> - Ls = rpo(Blocks), +split_blocks(Ls, P, Blocks, Count) -> split_blocks_1(Ls, P, Blocks, Count). -spec trim_unreachable(SSA0) -> SSA when @@ -601,14 +598,13 @@ used(#b_switch{arg=#b_var{}=V}) -> [V]; used(_) -> []. --spec definitions(Blocks :: block_map()) -> definition_map(). -definitions(Blocks) -> - Top = rpo(Blocks), +-spec definitions(Labels :: [label()], Blocks :: block_map()) -> definition_map(). +definitions(Labels, Blocks) -> fold_instrs(fun(#b_set{ dst = Var }=I, Acc) -> Acc#{Var => I}; (_Terminator, Acc) -> Acc - end, Top, #{}, Blocks). + end, Labels, #{}, Blocks). %% uses(Labels, BlockMap) -> UsageMap %% Traverse the blocks given by labels and builds a usage map @@ -630,15 +626,15 @@ fold_uses_block(Lbl, #b_blk{is=Is,last=Last}, UseMap0) -> end, F(Last, foldl(F, UseMap0, Is)). --spec merge_blocks(block_map()) -> block_map(). +-spec merge_blocks([label()], block_map()) -> block_map(). -merge_blocks(Blocks) -> +merge_blocks(Labels, Blocks) -> Preds = predecessors(Blocks), %% We must traverse the blocks in reverse postorder to avoid %% embedding succeeded:guard instructions into the middle of %% blocks when this function is called from beam_ssa_bool. - merge_blocks_1(rpo(Blocks), Preds, Blocks). + merge_blocks_1(Labels, Preds, Blocks). %%% %%% Internal functions. diff --git a/lib/compiler/src/beam_ssa_bool.erl b/lib/compiler/src/beam_ssa_bool.erl index 5fa60c3b19..b3b41e68c3 100644 --- a/lib/compiler/src/beam_ssa_bool.erl +++ b/lib/compiler/src/beam_ssa_bool.erl @@ -160,7 +160,7 @@ opt_function(#b_function{bs=Blocks0,cnt=Count0}=F) -> %% To ensure that, trim before merging. Blocks3 = beam_ssa:trim_unreachable(Blocks2), - Blocks = beam_ssa:merge_blocks(Blocks3), + Blocks = beam_ssa:merge_blocks(beam_ssa:rpo(Blocks3), Blocks3), F#b_function{bs=Blocks,cnt=Count}; true -> %% There are no boolean operators that can be optimized in @@ -1504,7 +1504,7 @@ join_inits_1([], VarMap) -> %%% %%% We don't try merge blocks during the conversion because it would %%% be difficult to keep phi nodes up to date. We will call -%%% beam_ssa:merge_blocks/1 before returning from this pass to do all +%%% beam_ssa:merge_blocks/2 before returning from this pass to do all %%% block merging. %%% diff --git a/lib/compiler/src/beam_ssa_bsm.erl b/lib/compiler/src/beam_ssa_bsm.erl index 9984c3586f..59872290a6 100644 --- a/lib/compiler/src/beam_ssa_bsm.erl +++ b/lib/compiler/src/beam_ssa_bsm.erl @@ -459,12 +459,14 @@ combine_matches(#b_function{bs=Blocks0,cnt=Counter0}=F, ModInfo) -> {Block0#b_blk{is=Is}, State} end, RPO, - #cm{ definitions = beam_ssa:definitions(Blocks0), + #cm{ definitions = beam_ssa:definitions(RPO, Blocks0), dominators = Dominators, blocks = Blocks0 }, Blocks0), - Blocks2 = beam_ssa:rename_vars(State#cm.renames, [0], Blocks1), + %% The fun in mapfold_blocks does not update terminators, + %% so we can reuse the RPO computed for Blocks0. + Blocks2 = beam_ssa:rename_vars(State#cm.renames, RPO, Blocks1), {Blocks, Counter} = alias_matched_binaries(Blocks2, Counter0, State#cm.match_aliases), @@ -852,10 +854,10 @@ skip_outgoing_tail_extraction({Fs0, ModInfo}) -> skip_outgoing_tail_extraction(#b_function{bs=Blocks0}=F, ModInfo) -> case funcinfo_get(F, has_bsm_ops, ModInfo) of true -> - State0 = #sote{ definitions = beam_ssa:definitions(Blocks0), + RPO = beam_ssa:rpo(Blocks0), + State0 = #sote{ definitions = beam_ssa:definitions(RPO, Blocks0), mod_info = ModInfo }, - RPO = beam_ssa:rpo(Blocks0), {Blocks1, State} = beam_ssa:mapfold_instrs( fun sote_rewrite_calls/2, RPO, State0, Blocks0), diff --git a/lib/compiler/src/beam_ssa_opt.erl b/lib/compiler/src/beam_ssa_opt.erl index e08f60d7b3..3cd25ff273 100644 --- a/lib/compiler/src/beam_ssa_opt.erl +++ b/lib/compiler/src/beam_ssa_opt.erl @@ -453,7 +453,8 @@ ssa_opt_trim_unreachable({#opt_st{ssa=Blocks}=St, FuncDb}) -> {St#opt_st{ssa=beam_ssa:trim_unreachable(Blocks)}, FuncDb}. ssa_opt_merge_blocks({#opt_st{ssa=Blocks0}=St, FuncDb}) -> - Blocks = beam_ssa:merge_blocks(Blocks0), + RPO = beam_ssa:rpo(Blocks0), + Blocks = beam_ssa:merge_blocks(RPO, Blocks0), {St#opt_st{ssa=Blocks}, FuncDb}. %%% @@ -472,7 +473,8 @@ ssa_opt_split_blocks({#opt_st{ssa=Blocks0,cnt=Count0}=St, FuncDb}) -> (#b_set{op=make_fun}) -> true; (_) -> false end, - {Blocks,Count} = beam_ssa:split_blocks(P, Blocks0, Count0), + RPO = beam_ssa:rpo(Blocks0), + {Blocks,Count} = beam_ssa:split_blocks(RPO, P, Blocks0, Count0), {St#opt_st{ssa=Blocks,cnt=Count}, FuncDb}. %%% diff --git a/lib/compiler/src/beam_ssa_pre_codegen.erl b/lib/compiler/src/beam_ssa_pre_codegen.erl index 57fbc33558..78f9571e46 100644 --- a/lib/compiler/src/beam_ssa_pre_codegen.erl +++ b/lib/compiler/src/beam_ssa_pre_codegen.erl @@ -750,7 +750,8 @@ sanitize([], Count, Blocks0, Values) -> map_size(Values) =:= 0 -> Blocks0; true -> - beam_ssa:rename_vars(Values, [0], Blocks0) + RPO = beam_ssa:rpo(Blocks0), + beam_ssa:rename_vars(Values, RPO, Blocks0) end, %% Unreachable blocks can cause problems for the dominator calculations. @@ -1511,7 +1512,8 @@ fix_receives_1([{L,Blk}|Ls], Blocks0, Count0) -> #b_blk{is=[#b_set{op=peek_message}|_]} -> Rm = find_rm_blocks(L, Blocks0), LoopExit = find_loop_exit(Rm, Blocks0), - Defs0 = beam_ssa:def([L], Blocks0), + RPO = beam_ssa:rpo([L], Blocks0), + Defs0 = beam_ssa:def(RPO, Blocks0), CommonUsed = recv_common(Defs0, LoopExit, Blocks0), {Blocks1,Count1} = recv_crit_edges(Rm, LoopExit, Blocks0, Count0), {Blocks2,Count2} = recv_fix_common(CommonUsed, LoopExit, Rm, @@ -1530,7 +1532,8 @@ recv_common(_Defs, none, _Blocks) -> %% in the tail position of a function. []; recv_common(Defs, Exit, Blocks) -> - {ExitDefs,ExitUnused} = beam_ssa:def_unused([Exit], Defs, Blocks), + RPO = beam_ssa:rpo([Exit], Blocks), + {ExitDefs,ExitUnused} = beam_ssa:def_unused(RPO, Defs, Blocks), Def = ordsets:subtract(Defs, ExitDefs), ordsets:subtract(Def, ExitUnused). @@ -1592,7 +1595,8 @@ rce_reroute_terminator(#b_switch{list=List0}=Last, Exit, New) -> recv_fix_common([Msg0|T], Exit, Rm, Blocks0, Count0) -> {Msg,Count1} = new_var('@recv', Count0), - Blocks1 = beam_ssa:rename_vars(#{Msg0=>Msg}, [Exit], Blocks0), + RPO = beam_ssa:rpo([Exit], Blocks0), + Blocks1 = beam_ssa:rename_vars(#{Msg0=>Msg}, RPO, Blocks0), N = length(Rm), {MsgVars,Count} = new_vars(duplicate(N, '@recv'), Count1), PhiArgs = fix_exit_phi_args(MsgVars, Rm, Exit, Blocks1), @@ -1607,7 +1611,8 @@ recv_fix_common([], _, _, Blocks, Count) -> recv_fix_common_1([V|Vs], [Rm|Rms], Msg, Blocks0) -> Ren = #{Msg=>V}, - Blocks1 = beam_ssa:rename_vars(Ren, [Rm], Blocks0), + RPO = beam_ssa:rpo([Rm], Blocks0), + Blocks1 = beam_ssa:rename_vars(Ren, RPO, Blocks0), #b_blk{is=Is0} = Blk0 = map_get(Rm, Blocks1), Copy = #b_set{op=copy,dst=V,args=[Msg]}, Is = insert_after_phis(Is0, [Copy]), @@ -1637,12 +1642,13 @@ exit_predecessors([], _Exit, _Blocks) -> []. %% later used within a clause of the receive. fix_receive([L|Ls], Defs, Blocks0, Count0) -> - {RmDefs,Unused} = beam_ssa:def_unused([L], Defs, Blocks0), + RPO = beam_ssa:rpo([L], Blocks0), + {RmDefs,Unused} = beam_ssa:def_unused(RPO, Defs, Blocks0), Def = ordsets:subtract(Defs, RmDefs), Used = ordsets:subtract(Def, Unused), {NewVars,Count} = new_vars([Base || #b_var{name=Base} <- Used], Count0), Ren = zip(Used, NewVars), - Blocks1 = beam_ssa:rename_vars(Ren, [L], Blocks0), + Blocks1 = beam_ssa:rename_vars(Ren, RPO, Blocks0), #b_blk{is=Is0} = Blk1 = map_get(L, Blocks1), CopyIs = [#b_set{op=copy,dst=New,args=[Old]} || {Old,New} <- Ren], Is = insert_after_phis(Is0, CopyIs), @@ -1667,8 +1673,8 @@ find_loop_exit([_,_|_]=RmBlocks, Blocks) -> RPO = beam_ssa:rpo(Blocks), {Dominators,_} = beam_ssa:dominators(RPO, Blocks), RmSet = cerl_sets:from_list(RmBlocks), - Rpo = beam_ssa:rpo(RmBlocks, Blocks), - find_loop_exit_1(Rpo, RmSet, Dominators, Blocks); + RmRPO = beam_ssa:rpo(RmBlocks, Blocks), + find_loop_exit_1(RmRPO, RmSet, Dominators, Blocks); find_loop_exit(_, _) -> %% There is (at most) a single clause. There is no common %% loop exit block. @@ -2342,10 +2348,11 @@ reserve_yregs(#st{frames=Frames}=St0) -> reserve_yregs_1(L, #st{ssa=Blocks0,cnt=Count0,res=Res0}=St) -> Blk = map_get(L, Blocks0), Yregs = ordsets:from_list(cerl_sets:to_list(beam_ssa:get_anno(yregs, Blk))), - {Def,Unused} = beam_ssa:def_unused([L], Yregs, Blocks0), + RPO = beam_ssa:rpo([L], Blocks0), + {Def,Unused} = beam_ssa:def_unused(RPO, Yregs, Blocks0), UsedYregs = ordsets:subtract(Yregs, Unused), DefBefore = ordsets:subtract(UsedYregs, Def), - {BeforeVars,Blocks,Count} = rename_vars(DefBefore, L, Blocks0, Count0), + {BeforeVars,Blocks,Count} = rename_vars(DefBefore, L, RPO, Blocks0, Count0), InsideVars = ordsets:subtract(UsedYregs, DefBefore), ResTryTags0 = reserve_try_tags(L, Blocks), ResTryTags = [{V,{Reg,Count}} || {V,Reg} <- ResTryTags0], @@ -2403,12 +2410,12 @@ update_act_map([L|Ls], Active0, ActMap0) -> end; update_act_map([], _, ActMap) -> ActMap. -rename_vars([], _, Blocks, Count) -> +rename_vars([], _, _, Blocks, Count) -> {[],Blocks,Count}; -rename_vars(Vs, L, Blocks0, Count0) -> +rename_vars(Vs, L, RPO, Blocks0, Count0) -> {NewVars,Count} = new_vars([Base || #b_var{name=Base} <- Vs], Count0), Ren = zip(Vs, NewVars), - Blocks1 = beam_ssa:rename_vars(Ren, [L], Blocks0), + Blocks1 = beam_ssa:rename_vars(Ren, RPO, Blocks0), #b_blk{is=Is0} = Blk0 = map_get(L, Blocks1), CopyIs = [#b_set{op=copy,dst=New,args=[Old]} || {Old,New} <- Ren], Is = insert_after_phis(Is0, CopyIs), @@ -2434,7 +2441,8 @@ frame_size(#st{frames=Frames,regs=Regs,ssa=Blocks0}=St) -> St#st{ssa=Blocks}. frame_size_1(L, Regs, Blocks0) -> - Def = beam_ssa:def([L], Blocks0), + RPO = beam_ssa:rpo([L], Blocks0), + Def = beam_ssa:def(RPO, Blocks0), Yregs0 = [map_get(V, Regs) || V <- Def, is_yreg(map_get(V, Regs))], Yregs = ordsets:from_list(Yregs0), FrameSize = length(ordsets:from_list(Yregs)), @@ -2480,7 +2488,8 @@ turn_yregs(#st{frames=Frames,regs=Regs0,ssa=Blocks}=St) -> Regs1 = foldl(fun(L, A) -> Blk = map_get(L, Blocks), FrameSize = beam_ssa:get_anno(frame_size, Blk), - Def = beam_ssa:def([L], Blocks), + RPO = beam_ssa:rpo([L], Blocks), + Def = beam_ssa:def(RPO, Blocks), [turn_yregs_1(Def, FrameSize, Regs0)|A] end, [], Frames), Regs = maps:merge(Regs0, maps:from_list(append(Regs1))), -- 2.26.2
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