Skip to content

Commit

Permalink
Merge branch 'bjorn/compiler/fix-mutable-variables/23/GH-6873/OTP-184…
Browse files Browse the repository at this point in the history
…70' into maint-23

* bjorn/compiler/fix-mutable-variables/23/GH-6873/OTP-18470:
  Eliminate "mutable variables"
  • Loading branch information
Erlang/OTP committed Jun 5, 2023
2 parents 1b18d30 + 4f271e5 commit 4229598
Show file tree
Hide file tree
Showing 3 changed files with 124 additions and 92 deletions.
187 changes: 99 additions & 88 deletions lib/compiler/src/v3_core.erl
Original file line number Diff line number Diff line change
Expand Up @@ -727,88 +727,47 @@ expr({call,L,FunExp,As0}, St0) ->
Lanno = lineno_anno(L, St2),
{#iapply{anno=#a{anno=Lanno},op=Fun,args=As1},Fps ++ Aps,St2};
expr({match,L,P0,E0}, St0) ->
%% First fold matches together to create aliases.
{P1,E1} = fold_match(E0, P0),
St1 = case P1 of
{var,_,'_'} -> St0#core{wanted=false};
_ -> St0
end,
{E2,Eps1,St2} = novars(E1, St1),
St3 = St2#core{wanted=St0#core.wanted},
{P2,St4} = try
pattern(P1, St3)
catch
throw:Thrown ->
{Thrown,St3}
end,
{Fpat,St5} = new_var(St4),
Lanno = lineno_anno(L, St5),
Fc = fail_clause([Fpat], Lanno, c_tuple([#c_literal{val=badmatch},Fpat])),
case P2 of
nomatch ->
%% The pattern will not match. We must take care here to
%% bind all variables that the pattern would have bound
%% so that subsequent expressions do not refer to unbound
%% variables.
%%
%% As an example, this code:
%%
%% [X] = {Y} = E,
%% X + Y.
%%
%% will be rewritten to:
%%
%% error({badmatch,E}),
%% case E of
%% {[X],{Y}} ->
%% X + Y;
%% Other ->
%% error({badmatch,Other})
%% end.
%%
St6 = add_warning(L, nomatch, St5),
{Expr,Eps3,St7} = safe(E1, St6),
SanPat0 = sanitize(P1),
{SanPat,St} = pattern(SanPat0, St7),
Badmatch = c_tuple([#c_literal{val=badmatch},Expr]),
Fail = #iprimop{anno=#a{anno=Lanno},
name=#c_literal{val=match_fail},
args=[Badmatch]},
Eps = Eps3 ++ [Fail],
{#imatch{anno=#a{anno=Lanno},pat=SanPat,arg=Expr,fc=Fc},Eps,St};
Other when not is_atom(Other) ->
%% We must rewrite top-level aliases to lets to avoid unbound
%% variables in code such as:
%%
%% <<42:Sz>> = Sz = B
%%
%% If we would keep the top-level aliases the example would
%% be translated like this:
%%
%% case B of
%% <Sz = #{#<42>(Sz,1,'integer',['unsigned'|['big']])}#>
%% when 'true' ->
%% .
%% .
%% .
%%
%% Here the variable Sz would be unbound in the binary pattern.
%%
%% Instead we bind Sz in a let to ensure it is bound when
%% used in the binary pattern:
St1 = set_wanted(P0, St0),
case fold_match(E0, P0) of
{{sequential_match,_,_,_}=P1,E1} ->
%% Matching of an expression to more than one pattern. Example:
%%
%% let <Sz> = B
%% in case Sz of
%% <#{#<42>(Sz,1,'integer',['unsigned'|['big']])}#>
%% when 'true' ->
%% .
%% .
%% .
%% #rec{f=Val} = A = Expr
{E2,Eps1,St2} = safe(E1, St1),
St3 = St2#core{wanted=St0#core.wanted},

%% If necessary, bind the expression to a variable to ensure it is
%% only evaluted once.
{Var,Eps2,St4} =
case E2 of
#c_var{} ->
{E2,[],St3};
_ ->
{Var0,StInt} = new_var(St3),
{Var0,[#iset{var=Var0,arg=E2}],StInt}
end,

%% Rewrite to a begin/end block matching one pattern at the time
%% (using the `single_match` operator). Example:
%%
{P3,E3,Eps2} = letify_aliases(P2, E2),
Eps = Eps1 ++ Eps2,
{#imatch{anno=#a{anno=Lanno},pat=P3,arg=E3,fc=Fc},Eps,St5}
%% begin
%% V = Expr,
%% A = V,
%% #rec{f=Val} = V
%% end
Block = blockify(L, P1, Var),
{E3,Eps3,St5} = expr({block,L,Block}, St4),
{E3,Eps1 ++ Eps2 ++ Eps3,St5};
{P0,E1} ->
%% Matching of an expression to a single pattern. Example:
%% {A,B} = Expr
{E2,Eps1,St2} = novars(E1, St1),
St3 = St2#core{wanted=St0#core.wanted},
{E3,Eps2,St4} = single_match(L, P0, E2, St3),
{E3,Eps1 ++ Eps2,St4}
end;
expr({single_match,L,P,#c_var{}=E}, St0) ->
single_match(L, P, E, St0);
expr({op,_,'++',{lc,Llc,E,Qs0},More}, St0) ->
%% Optimise '++' here because of the list comprehension algorithm.
%%
Expand Down Expand Up @@ -849,11 +808,63 @@ expr({op,L,Op,L0,R0}, St0) ->
module=#c_literal{anno=LineAnno,val=erlang},
name=#c_literal{anno=LineAnno,val=Op},args=As},Aps,St1}.

letify_aliases(#c_alias{var=V,pat=P0}, E0) ->
{P1,E1,Eps0} = letify_aliases(P0, V),
{P1,E1,[#iset{var=V,arg=E0}|Eps0]};
letify_aliases(P, E) ->
{P,E,[]}.
blockify(L0, {sequential_match,_L1,First,Then}, E) ->
[{single_match,L0,First,E}|blockify(L0, Then, E)];
blockify(L, P, E) ->
[{single_match,L,P,E}].

%% single_match(Line, AbstractPattern, CoreExpr, State0) -> {Expr,Pre,State}.
%% Generate the code for matching an expression against a single pattern.
single_match(L, P0, E, St0) ->
{Fpat,St1} = new_var(St0),
Lanno = lineno_anno(L, St1),
Fc = fail_clause([Fpat], Lanno, c_tuple([#c_literal{val=badmatch},Fpat])),
try pattern(P0, St1) of
{P1,St2} ->
St3 = set_wanted(P0, St2),
St4 = St3#core{wanted=St0#core.wanted},
{#imatch{anno=#a{anno=Lanno},pat=P1,arg=E,fc=Fc},[],St4}
catch
throw:nomatch ->
%% The pattern will not match. We must take care here to
%% bind all variables that the pattern would have bound
%% so that subsequent expressions do not refer to unbound
%% variables.
%%
%% As an example, this code:
%%
%% ([X] = {Y}) = E,
%% X + Y.
%%
%% will be rewritten to:
%%
%% error({badmatch,E}),
%% case E of
%% {[X],{Y}} ->
%% X + Y;
%% Other ->
%% error({badmatch,Other})
%% end.
%%
St2 = add_warning(L, nomatch, St1),
{Expr,Eps0,St3} = force_safe(E, St2),
SanPat0 = sanitize(P0),
{SanPat,St} = pattern(SanPat0, St3),
Badmatch = c_tuple([#c_literal{val=badmatch},Expr]),
Fail = #iprimop{anno=#a{anno=Lanno},
name=#c_literal{val=match_fail},
args=[Badmatch]},
Eps = Eps0 ++ [Fail],
{#imatch{anno=#a{anno=Lanno},pat=SanPat,arg=Expr,fc=Fc},Eps,St}
end.

%% set_wanted(Pattern, St) -> St'.
%% Suppress warnings for expressions that are bound to the '_'
%% variable. (In OTP 24 and later, variables that begin with '_' will
%% also suppress warnings.)
set_wanted({var,_,'_'}, St) ->
St#core{wanted=false};
set_wanted(_, St) -> St.

%% sanitize(Pat) -> SanitizedPattern
%% Rewrite Pat so that it will be accepted by pattern/2 and will
Expand Down Expand Up @@ -1948,10 +1959,10 @@ is_safe(_) -> false.
%% fold_match(MatchExpr, Pat) -> {MatchPat,Expr}.
%% Fold nested matches into one match with aliased patterns.

fold_match({match,L,P0,E0}, P) ->
{P1,E1} = fold_match(E0, P),
{{match,L,P0,P1},E1};
fold_match(E, P) -> {P,E}.
fold_match({match, L, P, E}, E0) ->
fold_match(E, {sequential_match, L, P, E0});
fold_match(E, E0) ->
{E0, E}.

%% pattern(Pattern, State) -> {CorePat,[PreExp],State}.
%% Transform a pattern by removing line numbers. We also normalise
Expand Down
26 changes: 24 additions & 2 deletions lib/compiler/test/match_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,8 @@
selectify/1,deselectify/1,underscore/1,match_map/1,map_vars_used/1,
coverage/1,grab_bag/1,literal_binary/1,
unary_op/1,eq_types/1,match_after_return/1,match_right_tuple/1,
tuple_size_in_try/1,match_boolean_list/1]).
tuple_size_in_try/1,match_boolean_list/1,
mutable_variables/1]).

-include_lib("common_test/include/ct.hrl").

Expand All @@ -43,7 +44,8 @@ groups() ->
underscore,match_map,map_vars_used,coverage,
grab_bag,literal_binary,unary_op,eq_types,
match_after_return,match_right_tuple,
tuple_size_in_try,match_boolean_list]}].
tuple_size_in_try,match_boolean_list,
mutable_variables]}].


init_per_suite(Config) ->
Expand Down Expand Up @@ -1018,4 +1020,24 @@ match_boolean_list(Config) when is_list(Config) ->
[false | _] -> ok
end.

%% GH-6873. Bound variables would be overwritten.
mutable_variables(_Config) ->
{'EXIT',{{badmatch,0},_}} = (catch mutable_variables_1()),

F = fun() -> id({tag,whatever}) end,
whatever = mutable_variables_2(id({tag,whatever}), F),
{'EXIT',{{badmatch,{tag,whatever}},_}} = (catch mutable_variables_2(id(a), F)),

ok.

mutable_variables_1() ->
Zero = 0,
One = 1,
Result = One = Zero,
{Result,One,Zero}.

mutable_variables_2(Middle, Fun) ->
{tag,V} = Middle = Fun(),
V.

id(I) -> I.
3 changes: 1 addition & 2 deletions lib/compiler/test/warnings_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -99,8 +99,7 @@ pattern(Config) when is_list(Config) ->
[warn_unused_vars],
{warnings,
[{2,v3_core,nomatch},
{6,v3_core,nomatch},
{11,v3_core,nomatch} ] }}],
{6,v3_core,nomatch} ] }}],
[] = run(Config, Ts),
ok.

Expand Down

0 comments on commit 4229598

Please sign in to comment.