Skip to content

Commit

Permalink
Merge branch 'maint'
Browse files Browse the repository at this point in the history
* maint:
  beam_ssa_codegen: Ensure that indexes are unique in update_record
  • Loading branch information
jhogberg committed Oct 4, 2024
2 parents 0c610c9 + 4afa158 commit 0354caf
Show file tree
Hide file tree
Showing 2 changed files with 25 additions and 8 deletions.
15 changes: 9 additions & 6 deletions lib/compiler/src/beam_ssa_codegen.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1378,7 +1378,7 @@ cg_block([#cg_set{op=update_record,dst=Dst0,args=Args0,anno=Anno}|T], Context, S
Args = typed_args(Args0, Anno, St0),
Dst = beam_arg(Dst0, St0),
[Hint,{integer,Size},Src|Ss0] = Args,
Ss = cg_update_record_list(Ss0, []),
Ss = cg_update_record_list(Ss0),
I = {update_record,Hint,Size,Src,Dst,{list,Ss}},
{Is1,St} = cg_block(T, Context, St0),
{[I|Is1],St};
Expand Down Expand Up @@ -1916,12 +1916,15 @@ cg_test(raw_raise, _Fail, Args, Dst, _I) ->
cg_test(resume, _Fail, [_,_]=Args, Dst, _I) ->
cg_instr(resume, Args, Dst).

cg_update_record_list([{integer, Index}, Value], []) ->
cg_update_record_list([{integer, Index}, Value]) ->
[Index, Value];
cg_update_record_list([{integer, Index}, Value | Updates], Acc) ->
cg_update_record_list(Updates, [{Index, Value} | Acc]);
cg_update_record_list([], Acc) ->
append([[Index, Value] || {Index, Value} <- sort(Acc)]).
cg_update_record_list([_,_|_]=Updates) ->
cg_update_record_list_1(Updates, #{}).

cg_update_record_list_1([{integer, Index}, Value | Updates], Acc) ->
cg_update_record_list_1(Updates, Acc#{ Index => Value });
cg_update_record_list_1([], Acc) ->
append([[Index, Value] || Index := Value <- maps:iterator(Acc, ordered)]).

cg_bs_get(Fail, #cg_set{dst=Dst0,args=Args,anno=Anno}=Set, St) ->
[{atom,Type}|Ss0] = typed_args(Args, Anno, St),
Expand Down
18 changes: 16 additions & 2 deletions lib/compiler/test/record_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,7 @@
errors/1,record_test_2/1,record_test_3/1,record_access_in_guards/1,
guard_opt/1,eval_once/1,foobar/1,missing_test_heap/1,
nested_access/1,coverage/1,grab_bag/1,slow_compilation/1,
record_updates/1]).
record_updates/1, duplicate_update_record/1]).

init_per_testcase(_Case, Config) ->
Config.
Expand All @@ -49,7 +49,7 @@ groups() ->
[errors,record_test_2,record_test_3,
record_access_in_guards,guard_opt,eval_once,foobar,
missing_test_heap,nested_access,coverage,grab_bag,
slow_compilation,record_updates]}].
slow_compilation,record_updates, duplicate_update_record]}].


init_per_suite(Config) ->
Expand Down Expand Up @@ -845,6 +845,20 @@ record_updates(_Config) ->

ok.

%% GH-8783: Duplicate indexes in update_record crashed the emulator.
duplicate_update_record(Config) when is_list(Config) ->
DuplicateUR0 = id({id(left), id(right)}),
{_, _} = DuplicateUR0,

DuplicateUR1 = erlang:setelement(2, DuplicateUR0, false),
DuplicateUR = erlang:setelement(2, DuplicateUR1, false),
{'EXIT', _} = catch duplicate_update_record_1(DuplicateUR),

ok.

duplicate_update_record_1(_) ->
erlang:error(crash).

%%%
%%% Common utilities.
%%%
Expand Down

0 comments on commit 0354caf

Please sign in to comment.