Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:24
erlang
2867-Remove-the-beam_peep-pass.patch
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 2867-Remove-the-beam_peep-pass.patch of Package erlang
From 8e4c66243cbb724c10c975a4ba9fd7b0bd81fc5d Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org> Date: Fri, 20 Aug 2021 07:19:57 +0200 Subject: [PATCH 7/7] Remove the beam_peep pass All optimizations in `beam_peep` have either been reimplemented as optimizations on SSA code or moved to other passes. --- lib/compiler/src/Makefile | 1 - lib/compiler/src/beam_clean.erl | 4 - lib/compiler/src/beam_peep.erl | 223 ---------------------------- lib/compiler/src/compile.erl | 3 - lib/compiler/src/compiler.app.src | 1 - lib/compiler/test/compile_SUITE.erl | 1 - lib/compiler/test/misc_SUITE.erl | 11 -- 7 files changed, 244 deletions(-) delete mode 100644 lib/compiler/src/beam_peep.erl diff --git a/lib/compiler/src/Makefile b/lib/compiler/src/Makefile index f195e16dc6..24414fef77 100644 --- a/lib/compiler/src/Makefile +++ b/lib/compiler/src/Makefile @@ -58,7 +58,6 @@ MODULES = \ beam_jump \ beam_listing \ beam_opcodes \ - beam_peep \ beam_ssa \ beam_ssa_bc_size \ beam_ssa_bool \ diff --git a/lib/compiler/src/beam_clean.erl b/lib/compiler/src/beam_clean.erl index 643cc1c386..e771818d10 100644 --- a/lib/compiler/src/beam_clean.erl +++ b/lib/compiler/src/beam_clean.erl @@ -22,7 +22,6 @@ -module(beam_clean). -export([module/2]). --export([clean_labels/1]). -spec module(beam_utils:module_code(), [compile:option()]) -> {'ok',beam_utils:module_code()}. @@ -98,9 +97,6 @@ add_to_work_list(F, {Fs,Used}=Sets) -> lc :: non_neg_integer() %Label counter }). --spec clean_labels([beam_utils:instruction()]) -> - {[beam_utils:instruction()],pos_integer()}. - clean_labels(Fs0) -> St0 = #st{lmap=[],entry=1,lc=1}, {Fs1,#st{lmap=Lmap0,lc=Lc}} = function_renumber(Fs0, St0, []), diff --git a/lib/compiler/src/beam_peep.erl b/lib/compiler/src/beam_peep.erl deleted file mode 100644 index da59aea2bd..0000000000 --- a/lib/compiler/src/beam_peep.erl +++ /dev/null @@ -1,223 +0,0 @@ -%% -%% %CopyrightBegin% -%% -%% Copyright Ericsson AB 2008-2020. All Rights Reserved. -%% -%% Licensed under the Apache License, Version 2.0 (the "License"); -%% you may not use this file except in compliance with the License. -%% You may obtain a copy of the License at -%% -%% http://www.apache.org/licenses/LICENSE-2.0 -%% -%% Unless required by applicable law or agreed to in writing, software -%% distributed under the License is distributed on an "AS IS" BASIS, -%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. -%% See the License for the specific language governing permissions and -%% limitations under the License. -%% -%% %CopyrightEnd% -%% - --module(beam_peep). - --export([module/2]). - --import(lists, [reverse/1,member/2,usort/1]). - --spec module(beam_utils:module_code(), [compile:option()]) -> - {'ok',beam_utils:module_code()}. - -module({Mod,Exp,Attr,Fs0,_}, _Opts) -> - %% First coalesce adjacent labels. - {Fs1,Lc} = beam_clean:clean_labels(Fs0), - - %% Do the peep hole optimizations. - Fs = [function(F) || F <- Fs1], - {ok,{Mod,Exp,Attr,Fs,Lc}}. - -function({function,Name,Arity,CLabel,Is0}) -> - try - Is1 = peep(Is0), - Is = beam_jump:remove_unused_labels(Is1), - {function,Name,Arity,CLabel,Is} - catch - Class:Error:Stack -> - io:fwrite("Function: ~w/~w\n", [Name,Arity]), - erlang:raise(Class, Error, Stack) - end. - - -%% Peep-hole optimizations suitable to perform when most of the -%% optimations passes have been run. -%% -%% (1) In a sequence of tests, we can remove any test instruction -%% that has been previously seen, because it will certainly -%% succeed. -%% -%% For instance, in the following code sequence -%% -%% is_eq_exact _Fail SomeRegister SomeLiteral -%% is_ne_exact _Fail SomeOtherRegister SomeOtherLiteral -%% is_eq_exact _Fail SomeRegister SomeLiteral -%% is_ne_exact _Fail SomeOtherRegister StillSomeOtherLiteral -%% -%% the third test is redundant. The code sequence will be produced -%% by a combination of semicolon and command guards, such as -%% -%% InEncoding =:= latin1, OutEncoding =:= unicode; -%% InEncoding =:= latin1, OutEncoding =:= utf8 -> -%% - -peep(Is) -> - peep(Is, gb_sets:empty(), []). - -peep([{bif,tuple_size,_,[_]=Ops,Dst}=I|Is], SeenTests0, Acc) -> - %% Pretend that we have seen {test,is_tuple,_,Ops}. - SeenTests1 = gb_sets:add({is_tuple,Ops}, SeenTests0), - %% Kill all remembered tests that depend on the destination register. - SeenTests = kill_seen(Dst, SeenTests1), - peep(Is, SeenTests, [I|Acc]); -peep([{bif,map_get,_,[Key,Map],Dst}=I|Is], SeenTests0, Acc) -> - %% Pretend that we have seen {test,has_map_fields,_,[Map,Key]} - SeenTests1 = gb_sets:add({has_map_fields,[Map,Key]}, SeenTests0), - %% Kill all remembered tests that depend on the destination register. - SeenTests = kill_seen(Dst, SeenTests1), - peep(Is, SeenTests, [I|Acc]); -peep([{bif,_,_,_,Dst}=I|Is], SeenTests0, Acc) -> - %% Kill all remembered tests that depend on the destination register. - SeenTests = kill_seen(Dst, SeenTests0), - peep(Is, SeenTests, [I|Acc]); -peep([{gc_bif,_,_,_,_,Dst}=I|Is], SeenTests0, Acc) -> - %% Kill all remembered tests that depend on the destination register. - SeenTests = kill_seen(Dst, SeenTests0), - peep(Is, SeenTests, [I|Acc]); -peep([{jump,{f,L}},{label,L}=I|Is], _, Acc) -> - %% Sometimes beam_jump has missed this optimization. - peep(Is, gb_sets:empty(), [I|Acc]); -peep([{select,select_val,R,F,Vls0}|Is], SeenTests0, Acc0) -> - case prune_redundant_values(Vls0, F) of - [] -> - %% No values left. Must convert to plain jump. - I = {jump,F}, - peep([I|Is], gb_sets:empty(), Acc0); - [{atom,_}=Value,Lbl] -> - %% Single value left. Convert to regular test. - Is1 = [{test,is_eq_exact,F,[R,Value]},{jump,Lbl}|Is], - peep(Is1, SeenTests0, Acc0); - [{integer,_}=Value,Lbl] -> - %% Single value left. Convert to regular test. - Is1 = [{test,is_eq_exact,F,[R,Value]},{jump,Lbl}|Is], - peep(Is1, SeenTests0, Acc0); - [{atom,B1},Lbl,{atom,B2},Lbl] when B1 =:= not B2 -> - %% Replace with is_boolean test. - Is1 = [{test,is_boolean,F,[R]},{jump,Lbl}|Is], - peep(Is1, SeenTests0, Acc0); - [_|_]=Vls -> - I = {select,select_val,R,F,Vls}, - peep(Is, gb_sets:empty(), [I|Acc0]) - end; -peep([{get_map_elements,Fail,Src,List}=I|Is], _SeenTests, Acc0) -> - SeenTests = gb_sets:empty(), - case simplify_get_map_elements(Fail, Src, List, Acc0) of - {ok,Acc} -> - peep(Is, SeenTests, Acc); - error -> - peep(Is, SeenTests, [I|Acc0]) - end; -peep([{test,has_map_fields,Fail,Ops}=I|Is], SeenTests, Acc0) -> - case simplify_has_map_fields(Fail, Ops, Acc0) of - {ok,Acc} -> - peep(Is, SeenTests, Acc); - error -> - peep(Is, SeenTests, [I|Acc0]) - end; -peep([{test,Op,_,Ops}=I|Is], SeenTests0, Acc) -> - case beam_utils:is_pure_test(I) of - false -> - %% Bit syntax matching, which may modify registers and/or - %% match state. Clear all information about tests that - %% has succeeded. - peep(Is, gb_sets:empty(), [I|Acc]); - true -> - case is_test_redundant(Op, Ops, SeenTests0) of - true -> - %% This test or a similar test has already succeeded and - %% is therefore redundant. - peep(Is, SeenTests0, Acc); - false -> - %% Remember that we have seen this test. - Test = {Op,Ops}, - SeenTests = gb_sets:insert(Test, SeenTests0), - peep(Is, SeenTests, [I|Acc]) - end - end; -peep([I|Is], _, Acc) -> - %% An unknown instruction. Throw away all information we - %% have collected about test instructions. - peep(Is, gb_sets:empty(), [I|Acc]); -peep([], _, Acc) -> reverse(Acc). - -is_test_redundant(Op, Ops, Seen) -> - gb_sets:is_element({Op,Ops}, Seen) orelse - is_test_redundant_1(Op, Ops, Seen). - -is_test_redundant_1(is_boolean, [R], Seen) -> - gb_sets:is_element({is_eq_exact,[R,{atom,false}]}, Seen) orelse - gb_sets:is_element({is_eq_exact,[R,{atom,true}]}, Seen); -is_test_redundant_1(_, _, _) -> false. - -kill_seen(Dst, Seen0) -> - gb_sets:from_ordset(kill_seen_1(gb_sets:to_list(Seen0), Dst)). - -kill_seen_1([{_,Ops}=Test|T], Dst) -> - case member(Dst, Ops) of - true -> kill_seen_1(T, Dst); - false -> [Test|kill_seen_1(T, Dst)] - end; -kill_seen_1([], _) -> []. - -prune_redundant_values([_Val,F|Vls], F) -> - prune_redundant_values(Vls, F); -prune_redundant_values([Val,Lbl|Vls], F) -> - [Val,Lbl|prune_redundant_values(Vls, F)]; -prune_redundant_values([], _) -> []. - -simplify_get_map_elements(Fail, Src, {list,[Key,Dst]}, - [{get_map_elements,Fail,Src,{list,List1}}|Acc]) -> - case are_keys_literals([Key]) andalso are_keys_literals(List1) andalso - not is_source_overwritten(Src, List1) of - true -> - case member(Key, List1) of - true -> - %% The key is already in the other list. That is - %% very unusual, because there are optimizations to get - %% rid of duplicate keys. Therefore, don't try to - %% do anything smart here; just keep the - %% get_map_elements instructions separate. - error; - false -> - List = [Key,Dst|List1], - {ok,[{get_map_elements,Fail,Src,{list,List}}|Acc]} - end; - false -> - error - end; -simplify_get_map_elements(_, _, _, _) -> error. - -simplify_has_map_fields(Fail, [Src|Keys0], - [{test,has_map_fields,Fail,[Src|Keys1]}|Acc]) -> - case are_keys_literals(Keys0) andalso are_keys_literals(Keys1) of - true -> - Keys = usort(Keys0 ++ Keys1), - {ok,[{test,has_map_fields,Fail,[Src|Keys]}|Acc]}; - false -> - error - end; -simplify_has_map_fields(_, _, _) -> error. - -are_keys_literals([{x,_}|_]) -> false; -are_keys_literals([{y,_}|_]) -> false; -are_keys_literals([_|_]) -> true. - -is_source_overwritten(Src, [_Key,Src]) -> true; -is_source_overwritten(_, _) -> false. diff --git a/lib/compiler/src/compile.erl b/lib/compiler/src/compile.erl index 7a36c6333a..ef421c20e7 100644 --- a/lib/compiler/src/compile.erl +++ b/lib/compiler/src/compile.erl @@ -916,8 +916,6 @@ asm_passes() -> {iff,dblk,{listing,"block"}}, {unless,no_jopt,{pass,beam_jump}}, {iff,djmp,{listing,"jump"}}, - {unless,no_peep_opt,{pass,beam_peep}}, - {iff,dpeep,{listing,"peep"}}, {pass,beam_clean}, {iff,dclean,{listing,"clean"}}, {unless,no_stack_trimming,{pass,beam_trim}}, @@ -2020,7 +2018,6 @@ pre_load() -> beam_jump, beam_kernel_to_ssa, beam_opcodes, - beam_peep, beam_ssa, beam_ssa_bc_size, beam_ssa_bool, diff --git a/lib/compiler/src/compiler.app.src b/lib/compiler/src/compiler.app.src index 08827c66b3..6aa4009645 100644 --- a/lib/compiler/src/compiler.app.src +++ b/lib/compiler/src/compiler.app.src @@ -34,7 +34,6 @@ beam_kernel_to_ssa, beam_listing, beam_opcodes, - beam_peep, beam_ssa, beam_ssa_bc_size, beam_ssa_bool, diff --git a/lib/compiler/test/compile_SUITE.erl b/lib/compiler/test/compile_SUITE.erl index 7ab621fab5..d9f1ba0a9d 100644 --- a/lib/compiler/test/compile_SUITE.erl +++ b/lib/compiler/test/compile_SUITE.erl @@ -486,7 +486,6 @@ do_file_listings(DataDir, PrivDir, [File|Files]) -> {dblk, ".block"}, {djmp, ".jump"}, {dclean, ".clean"}, - {dpeep, ".peep"}, {dopt, ".optimize"}, {diffable, ".S"}], p_listings(List, Simple, TargetDir), diff --git a/lib/compiler/test/misc_SUITE.erl b/lib/compiler/test/misc_SUITE.erl index 5f24fb1f27..ae5fff2ed3 100644 --- a/lib/compiler/test/misc_SUITE.erl +++ b/lib/compiler/test/misc_SUITE.erl @@ -257,17 +257,6 @@ silly_coverage(Config) when is_list(Config) -> TrimInput = BlockInput, expect_error(fun() -> beam_trim:module(TrimInput, []) end), - %% beam_peep. This is tricky. Use a select instruction with - %% an odd number of elements in the list to crash - %% prune_redundant_values/2 but not beam_clean:clean_labels/1. - PeepInput = {?MODULE,[{foo,0}],[], - [{function,foo,0,2, - [{label,1}, - {func_info,{atom,?MODULE},{atom,foo},0}, - {label,2},{select,select_val,r,{f,2},[{f,2}]}]}], - 2}, - expect_error(fun() -> beam_peep:module(PeepInput, []) end), - BeamZInput = {?MODULE,[{foo,0}],[], [{function,foo,0,2, [{label,1}, -- 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