Skip to content

Commit

Permalink
compiler alias analysis: Improve handling of Phi-instructions
Browse files Browse the repository at this point in the history
Stop treating Phi instructions as an extraction, instead make use of
the infrastructure used to derive the structure and alias status of
function arguments.

The sharing state database representation for the result of a Phi
instruction is the same as for a function argument of a function with
multiple call sites, where the concrete argument values at the call
sites are the value at the respective predecessor block.
  • Loading branch information
frej committed Aug 5, 2024
1 parent 7bd1ad7 commit eca5f59
Show file tree
Hide file tree
Showing 3 changed files with 80 additions and 4 deletions.
12 changes: 8 additions & 4 deletions lib/compiler/src/beam_ssa_alias.erl
Original file line number Diff line number Diff line change
Expand Up @@ -502,7 +502,7 @@ aa_is([_I=#b_set{dst=Dst,op=Op,args=Args,anno=Anno0}|Is], SS0, AAS0) ->
peek_message ->
{aa_set_aliased(Dst, SS0), AAS0};
phi ->
{aa_phi(Dst, Args, SS0, AAS0), AAS0};
aa_phi(Dst, Args, SS0, AAS0);
put_list ->
SS1 = beam_ssa_ss:add_var(Dst, unique, SS0),
Types =
Expand Down Expand Up @@ -1125,10 +1125,14 @@ aa_bif(Dst, Bif, Args, SS, _AAS) ->
aa_set_aliased([Dst|Args], SS)
end.

aa_phi(Dst, Args0, SS0, AAS) ->
aa_phi(Dst, Args0, SS0, #aas{cnt=Cnt0}=AAS) ->
%% TODO: Use type info?
Args = [V || {V,_} <- Args0],
SS = aa_alias_surviving_args(Args, {phi,Dst}, SS0, AAS),
aa_derive_from(Dst, Args, SS).
?DP("Phi~n"),
SS1 = aa_alias_surviving_args(Args, {phi,Dst}, SS0, AAS),
?DP(" after aa_alias_surviving_args:~n~s.~n", [beam_ssa_ss:dump(SS1)]),
{SS,Cnt} = beam_ssa_ss:phi(Dst, Args, SS1, Cnt0),
{SS,AAS#aas{cnt=Cnt}}.

aa_call(Dst, [#b_local{}=Callee|Args], Anno, SS0,
#aas{alias_map=AliasMap,analyzed=Analyzed,
Expand Down
15 changes: 15 additions & 0 deletions lib/compiler/src/beam_ssa_ss.erl
Original file line number Diff line number Diff line change
Expand Up @@ -43,6 +43,7 @@
merge_in_args/3,
new/0,
new/3,
phi/4,
prune/3,
set_call_result/4,
set_status/3,
Expand Down Expand Up @@ -450,6 +451,20 @@ accumulate_edges(V, State, Edges0) ->
new() ->
beam_digraph:new().

-spec phi(beam_ssa:b_var(), [beam_ssa:b_var()],
sharing_state(), non_neg_integer())
-> sharing_state().
phi(Dst, Args, State0, Cnt) ->
?assert_state(State0),
?DP("** phi **~n~s~n", [dump(State0)]),
?DP(" dst: ~p~n", [Dst]),
?DP(" args: ~p~n", [Args]),
Structure = foldl(fun(Arg, Acc) ->
merge_in_arg(Arg, Acc, ?ARGS_DEPTH_LIMIT, State0)
end, no_info, Args),
?DP(" structure: ~p~n", [Structure]),
new([Dst], [Structure], Cnt, State0).

%%%
%%% Throws `too_deep` if the depth of sharing state value chains
%%% exceeds SS_DEPTH_LIMIT.
Expand Down
57 changes: 57 additions & 0 deletions lib/compiler/test/beam_ssa_check_SUITE_data/phis.erl
Original file line number Diff line number Diff line change
@@ -0,0 +1,57 @@
%% Extracted from lib/syntax_tools/src/erl_recomment.erl to test
%% omissions in handling of Phi instructions.

%% =====================================================================
%% 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.
%%
%% Alternatively, you may use this file under the terms of the GNU Lesser
%% General Public License (the "LGPL") as published by the Free Software
%% Foundation; either version 2.1, or (at your option) any later version.
%% If you wish to allow use of your version of this file only under the
%% terms of the LGPL, you should delete the provisions above and replace
%% them with the notice and other provisions required by the LGPL; see
%% <http://www.gnu.org/licenses/>. If you do not delete the provisions
%% above, a recipient may use your version of this file under the terms of
%% either the Apache License or the LGPL.
%%
%% @copyright 1997-2006 Richard Carlsson
%% @author Richard Carlsson <[email protected]>
%% @end
%% =====================================================================

-module(phis).

-export([filter_forms/1]).

-record(filter, {file = undefined :: file:filename() | 'undefined',
line = 0 :: integer()}).

filter_forms(Fs) ->
filter_forms(Fs, #filter{}).

filter_forms([{A1, A2} | Fs], S) ->
%ssa% (_, Rec0) when post_ssa_opt ->
%ssa% Rec = update_record(inplace, 3, Rec0, ...),
%ssa% Phi = phi({Rec0, _}, {Rec, _}),
%ssa% _ = update_record(inplace, 3, Phi, ...).
S1 = case ex:f() of
undefined ->
S#filter{file = A1, line = A2};
_ ->
S
end,
if S1#filter.file =:= A1 ->
filter_forms(Fs, S1#filter{line = A2});
true ->
filter_forms(Fs, S1)
end;
filter_forms([], _) ->
[].

0 comments on commit eca5f59

Please sign in to comment.