Skip to content

Commit

Permalink
Eliminate crash for nested guards in record initialization
Browse files Browse the repository at this point in the history
Also fix other bugs in the `erl_expand_records` pass hidden behind the
original bug.

Closes #8190
  • Loading branch information
bjorng committed Mar 4, 2024
1 parent ab7b354 commit 1b23ddb
Show file tree
Hide file tree
Showing 3 changed files with 73 additions and 27 deletions.
26 changes: 19 additions & 7 deletions lib/stdlib/src/erl_expand_records.erl
Original file line number Diff line number Diff line change
Expand Up @@ -56,11 +56,13 @@ module has no references to records, attributes, or code.
%% Is is assumed that Fs is a valid list of forms. It should pass
%% erl_lint without errors.
module(Fs0, Opts0) ->
put(erl_expand_records_in_guard, false),
Opts = compiler_options(Fs0) ++ Opts0,
Dialyzer = lists:member(dialyzer, Opts),
Calltype = init_calltype(Fs0),
St0 = #exprec{compile = Opts, dialyzer = Dialyzer, calltype = Calltype},
{Fs,_St} = forms(Fs0, St0),
erase(erl_expand_records_in_guard),
Fs.

compiler_options(Forms) ->
Expand Down Expand Up @@ -209,12 +211,18 @@ normalise_test(tuple, 1) -> is_tuple;
normalise_test(Name, _) -> Name.

is_in_guard() ->
get(erl_expand_records_in_guard) =/= undefined.
get(erl_expand_records_in_guard).

in_guard(F) ->
undefined = put(erl_expand_records_in_guard, true),
InGuard = put(erl_expand_records_in_guard, true),
Res = F(),
true = erase(erl_expand_records_in_guard),
true = put(erl_expand_records_in_guard, InGuard),
Res.

not_in_guard(F) ->
InGuard = put(erl_expand_records_in_guard, false),
Res = F(),
false = put(erl_expand_records_in_guard, InGuard),
Res.

%% record_test(Anno, Term, Name, Vs, St) -> TransformedExpr
Expand Down Expand Up @@ -370,11 +378,15 @@ expr({'fun',Anno,{function,F,A}}=Fun0, St0) ->
expr({'fun',_,{function,_M,_F,_A}}=Fun, St) ->
{Fun,St};
expr({'fun',Anno,{clauses,Cs0}}, St0) ->
{Cs,St1} = clauses(Cs0, St0),
{{'fun',Anno,{clauses,Cs}},St1};
not_in_guard(fun() ->
{Cs,St1} = clauses(Cs0, St0),
{{'fun',Anno,{clauses,Cs}},St1}
end);
expr({named_fun,Anno,Name,Cs0}, St0) ->
{Cs,St1} = clauses(Cs0, St0),
{{named_fun,Anno,Name,Cs},St1};
not_in_guard(fun() ->
{Cs,St1} = clauses(Cs0, St0),
{{named_fun,Anno,Name,Cs},St1}
end);
expr({call,Anno,{atom,_,is_record},[A,{atom,_,Name}]}, St) ->
record_test(Anno, A, Name, St);
expr({call,Anno,{remote,_,{atom,_,erlang},{atom,_,is_record}},
Expand Down
9 changes: 2 additions & 7 deletions lib/stdlib/src/erl_lint.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2385,13 +2385,8 @@ is_guard_test(Expression, Forms, IsOverridden) ->
%% processing the forms until we'll know that the record
%% definitions are truly needed.
F = fun() ->
St = foldl(fun({attribute, _, record, _}=Attr0, St0) ->
Attr = set_file(Attr0, "none"),
attribute_state(Attr, St0);
(_, St0) ->
St0
end, start(), Forms),
St#lint.records
#{Name => {A,Fs} ||
{attribute, A, record, {Name, Fs}} <- Forms}
end,

is_guard_test2(NoFileExpression, {F,IsOverridden}).
Expand Down
65 changes: 52 additions & 13 deletions lib/stdlib/test/erl_expand_records_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -223,21 +223,60 @@ guard(Config) when is_list(Config) ->
%% Wildcard initialisation.
init(Config) when is_list(Config) ->
Ts = [
<<"
-record(r, {a,b,c,d = foo}).
t() ->
R = #r{_ = init, b = b},
#r{c = init, b = b, a = init} = R,
case R of
#r{b = b, _ = init} -> ok;
_ -> not_ok
end.
">>
],
~"""
-record(r, {a,b,c,d = foo}).
t() ->
R = #r{_ = init, b = b},
#r{c = init, b = b, a = init} = R,
case R of
#r{b = b, _ = init} -> ok;
_ -> not_ok
end.
""",
~"""
-record(r0, {a}).
-record(r1, {rf1 = (#r0{a = #{ok => ok || ok}})}).
t() ->
catch <<0 || #r1{}>>,
ok.
""",
~"""
-record(r0, {a}).
-record(r1, {
rf1 = fun
(+0.0) ->
(list_to_bitstring(ok))#r0.a;
(_) when ok ->
ok
end
}).
t() ->
catch <<0 || (#r1{})>>,
ok.
""",
~"""
-record(r0, {a}).
-record(r1, {
a = {
((ok)#r0{})#r0.a,
case whatever of
_ when cucumber ->
banan
end
}
}).
t() ->
catch #{ok => ok || #r1{}},
ok.
"""
],
run(Config, Ts),
ok.

%% Some patterns.
pattern(Config) when is_list(Config) ->
Ts = [
Expand Down

0 comments on commit 1b23ddb

Please sign in to comment.